try something
[mTask.git] / miTask.icl
1 module miTask
2
3 import StdDebug, StdMisc
4 from StdFunc import flip
5
6 import iTasks
7 import mTask
8
9 from Text import class Text(startsWith,concat,split,join), instance Text String
10
11 import Data.Tuple
12 import System.Directory
13
14 import iTasks.UI.Definition
15
16 import iTasks._Framework.TaskState
17 import iTasks._Framework.TaskServer
18 import iTasks._Framework.IWorld
19 import iTasks._Framework.Store
20
21 import TTY
22
23 derive class iTask Queue, TTYSettings, Parity, BaudRate, ByteSize
24 derive class iTask MTaskMSGRecv, MTaskMSGSend
25
26 :: *Resource | TTYd !*TTY
27
28 Start :: *World -> *World
29 Start world = startEngine (withShared ([], False, [], False) mTaskTask) world
30 //Start world = startEngine mTaskTask world
31 //
32 deviceSelectorNetwork :: Task (Int, String)
33 deviceSelectorNetwork = enterInformation "Port Number?" []
34 -&&- enterInformation "Network address" []
35
36 deviceSelectorSerial :: Task (String, TTYSettings)
37 deviceSelectorSerial = accWorld getDevices
38 >>= \dl->(enterChoice "Device" [] dl -&&- deviceSettings)
39 where
40 deviceSettings = updateInformation "Settings" [] zero
41
42 getDevices :: !*World -> *(![String], !*World)
43 getDevices w = case readDirectory "/dev" w of
44 (Error (errcode, errmsg), w) = abort errmsg
45 (Ok entries, w) = (map ((+++) "/dev/") (filter isTTY entries), w)
46 where
47 isTTY s = not (isEmpty (filter (flip startsWith s) prefixes))
48 prefixes = ["ttyS", "ttyACM", "ttyUSB", "tty.usbserial"]
49
50 derive class iTask SerTCP
51 :: SerTCP = Serial | TCP
52
53 mTaskTask :: (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
54 mTaskTask ch =
55 (enterInformation "Choose" [] >>= \st->case st of
56 Serial = deviceSelectorSerial >>= \(s,set)->syncSerialChannel s set decode encode ch
57 TCP = deviceSelectorNetwork >>= \(p,h)->syncNetworkChannel h p "\n" decode encode ch
58 ) ||-
59 sendMsg msgs ch ||-
60 (
61 (
62 consumeNetworkStream (processSDSs sdsShares messageShare) ch ||-
63 viewSharedInformation "channels" [ViewWith lens] ch ||-
64 viewSharedInformation "messages" [] messageShare ||-
65 viewSh sdsShares ch
66 ) >>* [OnAction ActionFinish (always shutDown)]
67 )
68 where
69 messageShare :: Shared [String]
70 messageShare = sharedStore "mTaskMessagesRecv" []
71
72 processSDSs :: [(Int, Shared Int)] (Shared [String]) [MTaskMSGRecv] -> Task ()
73 processSDSs _ _ [] = return ()
74 processSDSs s y [x:xs] = updateSDSs s y x >>= \_->processSDSs s y xs
75
76 updateSDSs :: [(Int, Shared Int)] (Shared [String]) MTaskMSGRecv -> Task ()
77 updateSDSs _ m (MTMessage s) = upd (\l->take 20 [s:l]) m @! ()
78 updateSDSs _ _ MTEmpty = return ()
79 updateSDSs [(id, sh):xs] m n=:(MTPub i d)
80 | id == i = set ((toInt d.[0])*265 + toInt d.[1]) sh @! ()
81 = updateSDSs xs m n
82
83 lens :: ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool) -> ([String], [String])
84 lens (r,_,s,_) = (f r, map toString s)
85 where
86 f [] = []
87 f [MTEmpty:xs] = f xs
88 f [x:xs] = [toString x:f xs]
89
90 viewSh :: [(Int, Shared Int)] (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
91 viewSh [] ch = return ()
92 viewSh [(i, sh):xs] ch
93 # sharename = "SDS-" +++ toString i
94 = (
95 viewSharedInformation ("SDS-" +++ toString i) [] sh ||-
96 forever (
97 enterInformation sharename []
98 >>* [OnAction ActionOk
99 (ifValue (\j->j>=1 && j <= 3)
100 (\c->set c sh
101 >>= \_->sendMsg (toSDSUpdate i c) ch
102 @! ()
103 )
104 )]
105 )
106 ) ||- viewSh xs ch
107
108 (msgs, sdsShares) = makeBytecode 500 bc
109
110 bc :: Main (ByteCode () Stmt)
111 bc = sds \x=1 In sds \pinnetje=1 In {main =
112 IF (digitalRead D3 ==. lit True) (
113 x =. x +. lit 1 :.
114 pub x
115 ) (
116 noOp
117 ) :.
118 IF (pinnetje ==. lit 1) (
119 digitalWrite D0 (lit True) :.
120 digitalWrite D1 (lit False) :.
121 digitalWrite D2 (lit False)
122 ) (
123 IF (pinnetje ==. lit 2) (
124 digitalWrite D0 (lit False) :.
125 digitalWrite D1 (lit True) :.
126 digitalWrite D2 (lit False)
127 ) (
128 digitalWrite D0 (lit False) :.
129 digitalWrite D1 (lit False) :.
130 digitalWrite D2 (lit True)
131 )
132 )}
133
134 makeBytecode :: Int (Main (ByteCode () Stmt)) -> ([MTaskMSGSend], [(Int, Shared Int)])
135 makeBytecode timeout bc
136 # (msgs, st) = toMessages timeout (toRealByteCode (unMain bc))
137 # shares = map (\(i,d)->(i, sdsFocus (s i) (memoryStore (s i) (Just (dd d))))) st.sdss
138 = (msgs, shares)
139 where
140 s i = "mTaskSDS-" +++ toString i
141 dd [x,y] = (toInt x)*265+(toInt y)
142
143
144 sendMsg :: [MTaskMSGSend] (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
145 sendMsg m ch = upd (\(r,rs,s,ss)->(r,rs,s ++ m,ss)) ch @! ()
146
147 syncSerialChannel :: String TTYSettings (String -> m) (n -> String) (Shared ([m],Bool,[n],Bool)) -> Task () | iTask m & iTask n
148 syncSerialChannel dev opts decodeFun encodeFun rw = Task eval
149 where
150 eval event evalOpts tree=:(TCInit taskId ts) iworld=:{IWorld|world}
151 = case TTYopen dev opts world of
152 (False, _, world)
153 # (err, world) = TTYerror world
154 = (ExceptionResult (exception err), {iworld & world=world})
155 (True, tty, world)
156 # iworld = {iworld & world=world, resources=Just (TTYd tty)}
157 = case addBackgroundTask 42 (BackgroundTask (serialDeviceBackgroundTask rw decodeFun encodeFun)) iworld of
158 (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
159 (Ok _, iworld) = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=True} NoRep (TCBasic taskId ts JSONNull False), iworld)
160
161 eval _ _ tree=:(TCBasic _ ts _ _) iworld
162 = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=False} NoRep tree, iworld)
163
164 eval event evalOpts tree=:(TCDestroy _) iworld=:{IWorld|resources,world}
165 # (TTYd tty) = fromJust resources
166 # (ok, world) = TTYclose tty world
167 # iworld = {iworld & world=world,resources=Nothing}
168 = case removeBackgroundTask 42 iworld of
169 (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
170 (Ok _, iworld) = (DestroyedResult, iworld)
171
172 serialDeviceBackgroundTask :: (Shared ([m],Bool,[n],Bool)) (String -> m) (n -> String) !*IWorld -> *IWorld
173 serialDeviceBackgroundTask rw de en iworld
174 = case read rw iworld of
175 (Error e, iworld) = abort "share couldn't be read"
176 (Ok (r,rs,s,ss), iworld)
177 # (Just (TTYd tty)) = iworld.resources
178 # tty = writet (map en s) tty
179 # (ml, tty) = case TTYavailable tty of
180 (False, tty) = ([], tty)
181 (_, tty)
182 # (l, tty) = TTYreadline tty
183 = ([de l], tty)
184 # iworld = {iworld & resources=Just (TTYd tty)}
185 = case write (r++ml,rs,[],ss) rw iworld of
186 (Error e, iworld) = abort "share couldn't be written"
187 (Ok _, iworld) = case notify rw iworld of
188 (Error e, iworld) = abort "share couldn't be notified"
189 (Ok _, iworld) = iworld
190 where
191 writet :: [String] !*TTY -> *TTY
192 writet [] t = t
193 writet [x:xs] t = writet xs (TTYwrite x t)
194
195
196 syncNetworkChannel :: String Int String (String -> m) (n -> String) (Shared ([m],Bool,[n],Bool)) -> Task () | iTask m & iTask n
197 syncNetworkChannel server port msgSeparator decodeFun encodeFun channel
198 = tcpconnect server port channel {ConnectionHandlers|onConnect=onConnect,whileConnected=whileConnected,onDisconnect=onDisconnect} @! ()
199 where
200 onConnect _ (received,receiveStopped,send,sendStopped)
201 = (Ok "",if (not (isEmpty send)) (Just (received,False,[],sendStopped)) Nothing, map encodeFun send,False)
202 whileConnected Nothing acc (received,receiveStopped,send,sendStopped)
203 = (Ok acc, Nothing, [], False)
204 whileConnected (Just newData) acc (received,receiveStopped,send,sendStopped)
205 # [acc:msgs] = reverse (split msgSeparator (concat [acc,newData]))
206 # write = if (not (isEmpty msgs && isEmpty send))
207 (Just (received ++ map decodeFun (reverse msgs),receiveStopped,[],sendStopped))
208 Nothing
209 = (Ok acc,write,map encodeFun send,False)
210
211 onDisconnect l (received,receiveStopped,send,sendStopped)
212 = (Ok l,Just (received,True,send,sendStopped))
213
214 consumeNetworkStream :: ([m] -> Task ()) (Shared ([m],Bool,[n],Bool)) -> Task () | iTask m & iTask n
215 consumeNetworkStream processTask channel
216 = ((watch channel >>* [OnValue (ifValue ifProcess process)]) <! id) @! ()
217 where
218 ifProcess (received,receiveStopped,_,_)
219 = receiveStopped || (not (isEmpty received))
220
221 process (received,receiveStopped,_,_)
222 = upd empty channel
223 >>| if (isEmpty received) (return ()) (processTask received)
224 @! receiveStopped
225
226 empty :: ([m],Bool,[n],Bool) -> ([m],Bool,[n],Bool)
227 empty (_,rs,s,ss) = ([],rs,s,ss)