36893a89d815e14e1f96936e3510f71138be0359
[ap2015.git] / a9 / mart / skeleton9.icl
1 module skeleton9
2
3
4 from iTasks import always, hasValue, :: TaskValue(..), :: Task, :: Stability,
5 :: TaskCont(..), :: Action, updateInformation, viewInformation, class
6 descr, instance descr String, :: UpdateOption, :: ViewOption(..), -||-,
7 -||, ||-, startEngine, class Publishable, >>*, class TFunctor,
8 instance TFunctor Task, class TApplicative, instance TApplicative Task,
9 instance Publishable Task, Void
10 import Data.Tuple, StdClass, StdList, iTasks._Framework.Generic, Text.JSON,
11 Data.Functor, Control.Applicative, Control.Monad, Data.Map
12 import qualified iTasks
13 import qualified Text
14 from Text import class Text, instance Text String
15 from StdFunc import o
16 import qualified Data.List as List
17
18 :: BM a b = {t :: a -> b, f :: b -> a}
19 bm :: BM a a
20 bm = {f=id, t=id}
21 :: Op = Pl | Mi | Ti
22 :: Set :== Expr [Int]
23 :: Element :== Expr Int
24 :: Expr a
25 = New (BM a [Int])
26 | Insert (BM a [Int]) Element Set
27 | Delete (BM a [Int]) Element Set
28 | Variable (BM a a) Ident
29 | Union (BM a [Int]) Set Set
30 | Difference (BM a [Int]) Set Set
31 | Intersection (BM a [Int]) Set Set
32 | Integer (BM a Int) Int
33 | Size (BM a Int) Set
34 | Oper (BM a Int) Element Op Element
35 | Assign (BM a a) Ident (Expr a)
36 new :== New bm
37 insert = Insert bm
38 delete = Delete bm
39 variable = Variable bm
40 union = Union bm
41 difference = Difference bm
42 intersection = Intersection bm
43 integer :== Integer bm
44 size = Size bm
45 oper = Oper bm
46 instance + Element where (+) x y = Oper bm x Pl y
47 instance - Element where (-) x y = Oper bm x Mi y
48 instance * Element where (*) x y = Oper bm x Ti y
49 (=.) infix 4
50 (=.) x y = Assign bm x y
51
52 print :: a -> String | show a
53 print x = 'Text'.concat (show x [])
54
55 class show a :: a [String] -> [String]
56 instance show Op where
57 show o l = case o of Pl = ["+":l]; Mi = ["-":l]; Ti = ["*":l];
58 instance show Int where show i l = [toString i:l]
59 instance show [Int] where show i l = [toString i:l]
60 instance show (Expr a) | show a where
61 show (New _) l = ["{}":l]
62 show (Insert _ e s) l = ["{":show e ["}|":show s l]]
63 show (Delete _ e s) l = ["{":show e ["}\\":show s l]]
64 show (Variable _ s) l = [s:l]
65 show (Union _ s1 s2) l = show s1 ["|":show s2 l]
66 show (Difference _ s1 s2) l = show s1 ["\\":show s2 l]
67 show (Intersection _ s1 s2) l = show s1 ["&":show s2 l]
68 show (Integer _ i) l = show i l
69 show (Size _ s) l = ["|":show s ["|":l]]
70 show (Oper _ e1 op e2) l = show e1 (show op (show e2 l))
71 show (Assign _ s e) l = [s:["=":show e l]]
72
73 // === State
74 :: Ident :== String
75 :: Val = I Int | S [Int]
76 :: State :== Map Ident Val
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 Val -> Sem Val
128 store i v = Sem \st.(Result v, put i v st)
129
130 read :: Ident -> Sem Val
131 read i = Sem \st.(maybe (Exception (i +++ " not found")) Result (get i st), st)
132
133 (>>.) infixl 1 :: (Sem Val) (Int -> Sem Val) -> Sem Val
134 (>>.) f g = f >>= \x.case x of
135 I i = g i
136 S s = fail ("Element expected instead of set")
137
138 (>>..) infixl 1 :: (Sem Val) ([Int] -> Sem Val) -> Sem Val
139 (>>..) f g = f >>= \x.case x of
140 S s = g s
141 I i = fail ("Set expected instead of element " +++ toString i)
142
143 // === semantics
144 eval :: (Expr a) -> Sem Val
145 eval (New _) = return (S [])
146 eval (Insert _ e s) = eval e >>. \a.eval s >>..
147 \x.return (S ('List'.union [a] x))
148 eval (Delete _ e s) = eval e >>. \a.eval s >>..
149 \x.return (S ('List'.delete a x))
150 eval (Variable _ i) = read i
151 eval (Assign _ v e) = eval e >>= store v
152 eval (Union _ s1 s2) = eval s1 >>.. \x.eval s2
153 >>.. \y.return (S ('List'.union x y))
154 eval (Difference _ s1 s2) = eval s1 >>.. \x.eval s2
155 >>.. \y.return (S ('List'.difference x y))
156 eval (Intersection _ s1 s2) = eval s1 >>.. \x.eval s2
157 >>.. \y.return (S ('List'.intersect x y))
158 eval (Integer _ i) = return (I i)
159 eval (Size _ s) = eval s >>.. \x.return (I (length x))
160 eval (Oper _ e1 o e2) = eval e1 >>. \a.eval e2 >>. \b.return (I (case o of
161 Pl = a+b
162 Mi = a-b
163 Ti = a*b))
164
165 evalExpr :: (Expr a) State -> (MaybeEx Val, State)
166 evalExpr expr st = let (Sem func) = eval expr in func st
167
168 //Start = size (integer 42)
169 Start = evalExpr (size (variable "x")) st
170 where
171 (_, st) = evalExpr ("x" =. size (insert (integer 42) new)) newMap