now with working gadt
[ap2015.git] / a9 / mart / skeleton9.icl
1 module skeleton9
2 //One does not go over 80chars.
3 //the true lambda character is the .
4
5 from iTasks import always, hasValue, :: TaskValue(..), :: Task, :: Stability,
6 :: TaskCont(..), :: Action, updateInformation, viewInformation, class
7 descr, instance descr String, :: UpdateOption, :: ViewOption(..), -||-,
8 -||, ||-, startEngine, class Publishable, >>*, class TFunctor,
9 instance TFunctor Task, class TApplicative, instance TApplicative Task,
10 instance Publishable Task, Void
11 import Data.Tuple, StdClass, StdList, iTasks._Framework.Generic, Text.JSON,
12 Data.Functor, Control.Applicative, Control.Monad, Data.Map, StdMisc
13 import qualified iTasks
14 import qualified Text
15 from Text import class Text, instance Text String
16 from StdFunc import o
17 import qualified Data.List as List
18
19 :: BM a b = {t :: a -> b, f :: b -> a}
20 bm :: BM a a
21 bm = {f=id, t=id}
22 :: Op = Pl | Mi | Ti
23 :: Set :== Expr [Int]
24 :: Element :== Expr Int
25 :: Expr a
26 = New (BM a [Int])
27 | Insert (BM a [Int]) Element Set
28 | Delete (BM a [Int]) Element Set
29 | Variable (BM a a) Ident
30 | Union (BM a [Int]) Set Set
31 | Difference (BM a [Int]) Set Set
32 | Intersection (BM a [Int]) Set Set
33 | Integer (BM a Int) Int
34 | Size (BM a Int) Set
35 | Oper (BM a Int) Element Op Element
36 | Assign (BM a a) Ident (Expr a)
37 new :== New bm
38 insert = Insert bm
39 delete = Delete bm
40 variable = Variable bm
41 union = Union bm
42 difference = Difference bm
43 intersection = Intersection bm
44 integer :== Integer bm
45 size = Size bm
46 oper = Oper bm
47 instance + Element where (+) x y = Oper bm x Pl y
48 instance - Element where (-) x y = Oper bm x Mi y
49 instance * Element where (*) x y = Oper bm x Ti y
50 (=.) infix 4
51 (=.) x y = Assign bm x y
52
53 print :: a -> String | show a
54 print x = 'Text'.concat (show x [])
55
56 class show a :: a [String] -> [String]
57 instance show Op where
58 show o l = case o of Pl = ["+":l]; Mi = ["-":l]; Ti = ["*":l];
59 instance show Int where show i l = [toString i:l]
60 instance show [Int] where show i l = [toString i:l]
61 instance show (Expr a) | show a where
62 show (New _) l = ["{}":l]
63 show (Insert _ e s) l = ["{":show e ["}|":show s l]]
64 show (Delete _ e s) l = ["{":show e ["}\\":show s l]]
65 show (Variable _ s) l = [s:l]
66 show (Union _ s1 s2) l = show s1 ["|":show s2 l]
67 show (Difference _ s1 s2) l = show s1 ["\\":show s2 l]
68 show (Intersection _ s1 s2) l = show s1 ["&":show s2 l]
69 show (Integer _ i) l = show i l
70 show (Size _ s) l = ["|":show s ["|":l]]
71 show (Oper _ e1 op e2) l = show e1 (show op (show e2 l))
72 show (Assign _ s e) l = [s:["=":show e l]]
73
74 // === State
75 :: Ident :== String
76 :: State :== Map Ident Dynamic
77 :: Sem a = Sem (State -> (MaybeEx a, State))
78 :: MaybeEx a = Result a | Exception String
79
80 // === state handling
81
82 instance Functor Sem where
83 fmap :: (a -> b) (Sem a) -> Sem b
84 fmap f (Sem sF) = Sem (appFst (fmap f) o sF)
85
86 instance Functor MaybeEx where
87 fmap :: (a -> b) (MaybeEx a) -> MaybeEx b
88 fmap f (Result a) = Result (f a)
89 fmap _ (Exception e) = Exception e
90
91 instance Applicative Sem where
92 pure :: a -> Sem a
93 pure a = Sem \st.(pure a, st)
94
95 (<*>) infixl 4 :: (Sem (a -> b)) (Sem a) -> Sem b
96 (<*>) (Sem sFA) (Sem sFB) = Sem newSF
97 where
98 newSF st
99 # (ra, st) = sFA st
100 # (rb, st) = sFB st
101 = (ra <*> rb, st)
102
103 instance Applicative MaybeEx where
104 pure :: a -> MaybeEx a
105 pure a = Result a
106
107 (<*>) infixl 4 :: (MaybeEx (a -> b)) (MaybeEx a) -> MaybeEx b
108 (<*>) (Result f) (Result x) = Result (f x)
109 (<*>) (Exception e) _ = Exception e
110 (<*>) _ (Exception e) = Exception e
111
112 instance Monad Sem where
113 bind :: (Sem a) (a -> Sem b) -> Sem b
114 bind (Sem sFA) f = Sem sF
115 where
116 sF st
117 # (mbA, st) = sFA st
118 = case mbA of
119 Result a
120 # (Sem sFB) = f a
121 = sFB st
122 Exception e = (Exception e, st)
123
124 fail :: String -> Sem a
125 fail msg = Sem \st.(Exception msg, st)
126
127 store :: Ident a -> Sem a | TC a
128 store i v = Sem \st.(Result v, put i (dynamic v) st)
129
130 read :: Ident -> Sem a | TC a
131 read i = Sem \st.case get i st of
132 Just (a :: a^) = (Result a, st)
133 Just d = (Exception ('Text'.concat ["expected ", toString expType, " got ",
134 toString (typeCodeOfDynamic d)]), st)
135 Nothing = (Exception "No variable with that name", st)
136 where
137 expType = typeCodeOfDynamic (dynamic undef :: a^)
138
139 // === semantics
140 eval :: (Expr a) -> Sem a | TC a
141 eval (New {f}) = return (f [])
142 eval (Variable {f} i) = read i
143 eval (Assign {f} v e) = eval e >>= \a.store v a
144 eval (Insert {f} e s) = eval e >>= \a.eval s
145 >>= \x.return (f ('List'.union [a] x))
146 eval (Delete {f} e s) = eval e >>= \a.eval s
147 >>= \x.return (f ('List'.delete a x))
148 eval (Union {f} s1 s2) = eval s1 >>= \x.eval s2
149 >>= \y.return (f ('List'.union x y))
150 eval (Difference {f} s1 s2) = eval s1 >>= \x.eval s2
151 >>= \y.return (f ('List'.difference x y))
152 eval (Intersection {f} s1 s2) = eval s1 >>= \x.eval s2
153 >>= \y.return (f ('List'.intersect x y))
154 eval (Integer {f} i) = return (f i)
155 eval (Size {f} s) = eval s >>= \x.return (f (length x))
156 eval (Oper {f} e1 o e2) = eval e1 >>= \a.eval e2 >>= \b.return (f (case o of
157 Pl = a+b
158 Mi = a-b
159 Ti = a*b))
160
161 evalExpr :: (Expr a) State -> (MaybeEx a, State) | TC a
162 evalExpr expr st = let (Sem func) = eval expr in func st
163
164 Start :: (MaybeEx Int, State)
165 Start = evalExpr (size (variable "x")) state
166 where
167 (_, state) = evalExpr ("x" =. (insert (integer 42) new)) newMap