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)
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
>>= \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..."
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
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
instance toString Gamma where
toString (mp, _) = concat
[concat [k, ": ", toString v, "\n"]\\(k, v) <- 'Map'.toList mp]
+
+
+// class free a :: a -> Env [a]