optimize store with const 0
This commit is contained in:
parent
0ddd95852e
commit
b5c52365b3
5
Eval.hs
5
Eval.hs
@ -51,7 +51,10 @@ instance Monad Turn where
|
||||
return x = Turn $ \game -> return (game, Right x)
|
||||
fail s = Turn $ \game -> return (game, Left s)
|
||||
|
||||
liftIO :: IO x -> Turn x
|
||||
class Monad m => MonadIO m where
|
||||
liftIO :: IO x -> m x
|
||||
|
||||
instance MonadIO Turn where
|
||||
liftIO f = Turn $ \game -> f >>= \x -> return (game, Right x)
|
||||
|
||||
apply :: Int -> Turn ()
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# OPTIONS -XTypeSynonymInstances #-}
|
||||
|
||||
module Lambda where
|
||||
|
||||
@ -81,7 +82,9 @@ copyTo src dst = if (src == dst) then [] else storeInt dst src ++ [MoveLeft Card
|
||||
store :: Int -> Term -> [Move]
|
||||
store pos (Const n) = storeInt pos n
|
||||
store pos (Apply (Prim c) t) = store pos t ++ [MoveLeft c pos]
|
||||
store pos (Apply (Const 0) t) = store pos t ++ [MoveLeft Card_Zero pos]
|
||||
store pos (Apply t (Prim c)) = store pos t ++ [MoveRight pos c]
|
||||
store pos (Apply t (Const 0)) = store pos t ++ [MoveRight pos Card_Zero]
|
||||
store pos (Prim c) = [MoveLeft Card_Zero pos, MoveRight pos c]
|
||||
store pos (Seq a b) = store pos (Apply (Apply (Apply (Prim Card_S) a) b) (Prim Card_Zero))
|
||||
store pos (Apply a b) = if (pos == 0) then store 1 (Apply a b) ++ copyTo 1 0 else store pos a ++ store (pos+1) b ++ copyTo (pos+1) 0 ++ [MoveLeft Card_K pos, MoveLeft Card_S pos, MoveRight pos Card_Get, MoveRight pos Card_Zero]
|
||||
|
Loading…
Reference in New Issue
Block a user