WOOPWOOP expressies typen, behalve func
authorpimjager <pim@pimjager.nl>
Wed, 13 Apr 2016 10:34:36 +0000 (12:34 +0200)
committerpimjager <pim@pimjager.nl>
Wed, 13 Apr 2016 10:34:36 +0000 (12:34 +0200)
AST.dcl
AST.icl
examples/varEx.spl
sem.dcl
sem.icl

diff --git a/AST.dcl b/AST.dcl
index f15690d..97741e5 100644 (file)
--- a/AST.dcl
+++ b/AST.dcl
@@ -43,3 +43,4 @@ from StdOverloaded import class toString
 instance toString AST
 instance toString Type
 instance toString Pos
+instance toString FieldSelector
diff --git a/AST.icl b/AST.icl
index b9b9417..b5f8ca0 100644 (file)
--- a/AST.icl
+++ b/AST.icl
@@ -76,6 +76,9 @@ instance print FieldSelector where
        print FieldSnd = print "snd"
        print FieldFst = print "fst"
 
+instance toString FieldSelector where
+    toString fs = concat $ print fs
+
 instance print VarDef where
        print (VarDef i fs) = printersperse "." [i:flatten $ map print fs]
 
index 951fd28..68aa4f6 100644 (file)
@@ -13,7 +13,13 @@ var h = 1 != 3;
 var j = 1 < 3;
 //var k = True < 3;
 
-//var l = 1:2:[];
+var l = 1:2:[];
+
+var m = 4;
+var n = m + 2;
+var q = v + 2;
+var z = !v;
+
 
 facR(n) :: Int -> Int {
     return 5;
diff --git a/sem.dcl b/sem.dcl
index a2bcd57..0332076 100644 (file)
--- a/sem.dcl
+++ b/sem.dcl
@@ -2,13 +2,13 @@ definition module sem
 
 import qualified Data.Map as Map
 from Data.Either import :: Either
-from AST import :: AST, :: Pos, :: Type
+from AST import :: AST, :: Pos, :: Type, :: FieldSelector
 from StdOverloaded import class toString
 
 :: SemError 
        = ParseError Pos String 
        | UnifyError Pos Type Type 
-       | UnifyErrorStub Type Type 
+    | FieldSelectorError Pos Type FieldSelector 
        | Error String
 :: Gamma
 :: SemOutput :== Either [SemError] (AST, Gamma)
diff --git a/sem.icl b/sem.icl
index 1bedd62..75ecd37 100644 (file)
--- a/sem.icl
+++ b/sem.icl
@@ -52,11 +52,14 @@ instance toString SemError where
        toString (ParseError p e) = concat [
                toString p,"SemError: ParseError: ", e]
        toString (Error e) = "SemError: " +++ e
-       toString (UnifyErrorStub t1 t2) = toString (UnifyError {line=0,col=0} t1 t2)
        toString (UnifyError p t1 t2) = concat [
                toString p,
                "SemError: Cannot unify types. Expected: ",
                toString t1, ". Given: ", toString t2]
+    toString (FieldSelectorError p t fs) = concat [
+        toString p,
+        "SemError: Cannot select ", toString fs, " from type: ",
+        toString t]
 
 sem :: AST -> SemOutput
 sem (AST vd fd) = case runStateT m ('Map'.newMap, getRandomStream 1) of
@@ -107,12 +110,23 @@ typeExpr (Op2Expr p e1 BiCons e2) = typeExpr e1 >>= \t1-> typeExpr e2
     >>= \t2-> unify (ListType t1) t2
 typeExpr (EmptyListExpr p) = freshIdent >>= \frsh-> let t = IdType frsh in
     putIdent frsh t >>| pure t
-//typeExpr (FunExpr p FunCall) = undef
-//typeExpr (VarExpr Pos VarDef) = undef //when checking var-expr, be sure to
-    //put the infered type in the context
+//typeExpr (FunExpr p (FunCall f es)) = undef
+//ignore field selectors
+typeExpr (VarExpr p (VarDef ident fs)) = gets (\(st, r)->'Map'.get ident st)
+        >>= \mt->case mt of
+            Nothing = let t = IdType ident in putIdent ident t >>| pure t
+            Just t = unify t fs
 
 class unify a :: Type a -> Env Type
 
+instance unify [FieldSelector] where
+    unify t [] = pure t
+    unify (ListType t) [FieldHd:fs] = unify t fs
+    unify t=:(ListType _) [FieldTl:fs] = unify t fs
+    unify (TupleType (t, _)) [FieldFst:fs] = unify t fs
+    unify (TupleType (_, t)) [FieldSnd:fs] = unify t fs
+    unify t [fs:_] = liftT $ Left $ FieldSelectorError zero t fs
+
 instance unify Expr where
        unify (_ ->> _) e = liftT $ Left $ ParseError (extrPos e)
                        "Expression cannot be a higher order function. Yet..."
@@ -151,7 +165,7 @@ instance unify Type where
     unify (IdType i) t=:(IdType j) = replace i t >>| pure t
     unify t (IdType i) = unify (IdType i) t
     unify (IdType i) t = replace i t >>| pure t
-    //unify (ListType t1) (ListType t2) = unify t1 t2
+    unify (ListType t1) (ListType t2) = unify t1 t2 >>| (pure $ ListType t1)
        unify t1 t2 = liftT $ Left $ UnifyError zero t1 t2
 
 instance zero Pos where
@@ -159,6 +173,7 @@ instance zero Pos where
 
 decErr :: Expr SemError -> SemError
 decErr e (UnifyError _ t1 t2) = UnifyError (extrPos e) t1 t2
+decErr e (FieldSelectorError _ t fs) = FieldSelectorError (extrPos e) t fs
 decErr e (ParseError _ s) = ParseError (extrPos e) s
 decErr e err = err
 
@@ -180,3 +195,6 @@ extrPos (TupleExpr p _) = p
 instance toString Gamma where
        toString (mp, _) = concat
                [concat [k, ": ", toString v, "\n"]\\(k, v) <- 'Map'.toList mp]
+
+
+// class free a :: a -> Env [a]