Yippie
This commit is contained in:
@ -1,25 +1,48 @@
|
|||||||
{-# Language LambdaCase #-}
|
{-# Language LambdaCase, Strict #-}
|
||||||
module Assignment where
|
module Assignment where
|
||||||
|
|
||||||
import Chi
|
import Chi
|
||||||
|
import Control.Monad
|
||||||
|
import Control.Monad.Identity
|
||||||
|
import Debug.Trace (trace)
|
||||||
|
import Data.HashMap.Strict (HashMap)
|
||||||
|
import qualified Data.HashMap.Strict as HM
|
||||||
|
import Data.Functor ( (<&>) )
|
||||||
|
import Control.Monad.Identity (Identity(runIdentity))
|
||||||
|
|
||||||
subst :: Variable -> Exp -> Exp -> Exp
|
subst :: Variable -> Exp -> Exp -> Exp
|
||||||
subst var e = \case
|
subst var e = \case
|
||||||
Apply e1 e2 -> Apply (subst var e e1) (subst var e e2)
|
Apply e1 e2 -> Apply (subst var e e1) (subst var e e2)
|
||||||
Lambda x e' -> Lambda x $ if var /= x then (subst var e e') else e'
|
Lambda x e' -> Lambda x $ if var /= x then subst var e e' else e'
|
||||||
Var x -> if var == x then e else Var x
|
Var x -> if var == x then e else Var x
|
||||||
Const c es -> Const c $ map (subst var e) es
|
Const c es -> Const c $ map (subst var e) es
|
||||||
Rec x e' -> Rec x $ if var /= x then (subst var e e') else e'
|
Rec x e' -> Rec x $ if var /= x then subst var e e' else e'
|
||||||
Case e' branches -> Case (subst var e e') $ map substBr branches
|
Case e' bs -> Case (subst var e e') $ map substBr bs
|
||||||
where
|
where
|
||||||
substBr :: Br -> Br
|
substBr :: Br -> Br
|
||||||
substBr (Branch c vs e') = Branch c vs $ if var `notElem` vs then (subst var e e') else e'
|
substBr (Branch c vs e') = Branch c vs $ if var `notElem` vs then subst var e e' else e'
|
||||||
|
|
||||||
eval' :: Exp -> Reader (Map Variable Exp) Exp
|
lookupBranch :: Constructor -> [Br] -> Identity ([Variable], Exp)
|
||||||
eval' = undefined
|
lookupBranch c [] = error "No matching branch"
|
||||||
|
lookupBranch c ((Branch c' bs e):brs) = if c == c' then pure (bs,e) else lookupBranch c brs
|
||||||
|
|
||||||
|
eval' :: Exp -> Identity Exp
|
||||||
|
eval' = \case
|
||||||
|
e@(Apply e1 e2) -> eval' e1 >>= \case
|
||||||
|
Lambda x e' -> eval' e2 >>= eval' . flip (subst x) e'
|
||||||
|
_ -> error $ "Function was not function in evaluation: " <> show e
|
||||||
|
Const c es -> mapM eval' es <&> Const c
|
||||||
|
Rec x e -> eval' $ subst x (Rec x e) e
|
||||||
|
Case e bs -> eval' e >>= \case
|
||||||
|
Const c vs -> lookupBranch c bs >>= \case
|
||||||
|
(xs,e') ->
|
||||||
|
if length vs /= length xs then error "Not the same amount of arguments in case" else
|
||||||
|
eval' $ foldr (uncurry subst) e' (zip xs vs)
|
||||||
|
e -> error $ "Non const in case: " <> show e
|
||||||
|
x -> pure x
|
||||||
|
|
||||||
eval :: Exp -> Exp
|
eval :: Exp -> Exp
|
||||||
eval = undefined
|
eval = runIdentity . eval'
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = getLine >>= print . eval . parse
|
main = getLine >>= print . eval . parse
|
||||||
|
|||||||
@ -12,12 +12,12 @@ library
|
|||||||
hashable >= 1.4.7.0 && < 1.6,
|
hashable >= 1.4.7.0 && < 1.6,
|
||||||
mtl >= 2.2.2 && < 2.4,
|
mtl >= 2.2.2 && < 2.4,
|
||||||
pretty ^>= 1.1.3.6,
|
pretty ^>= 1.1.3.6,
|
||||||
QuickCheck ^>= 2.15.0.0,
|
QuickCheck ^>= 2.16.0.0,
|
||||||
transformers >= 0.5.6.2 && < 0.7,
|
transformers >= 0.5.6.2 && < 0.7,
|
||||||
unordered-containers ^>= 0.2.20
|
unordered-containers ^>= 0.2.20
|
||||||
build-tool-depends:
|
build-tool-depends:
|
||||||
alex:alex ^>= 3.5.2.0,
|
alex:alex ^>= 3.5.4.0,
|
||||||
happy:happy ^>= 2.1.5
|
happy:happy ^>= 2.1.7
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
AbsChi
|
AbsChi
|
||||||
Chi
|
Chi
|
||||||
@ -31,3 +31,5 @@ executable interpreter
|
|||||||
main-is: Assignment.hs
|
main-is: Assignment.hs
|
||||||
build-depends: base
|
build-depends: base
|
||||||
, chi
|
, chi
|
||||||
|
, mtl
|
||||||
|
, unordered-containers
|
||||||
|
|||||||
Reference in New Issue
Block a user