layout is working, now up to the communication
[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 from Data.Func import $
12 import Data.Tuple
13 import Data.List
14 import System.Directory
15
16 import iTasks.UI.Definition
17
18 import iTasks._Framework.TaskState
19 import iTasks._Framework.TaskServer
20 import iTasks._Framework.IWorld
21 import iTasks._Framework.Store
22
23
24 import TTY
25
26 derive class iTask Queue, TTYSettings, Parity, BaudRate, ByteSize
27 derive class iTask MTaskMSGRecv, MTaskMSGSend, SerTCP, UserLED
28
29 :: *Resource | TTYd !*TTY
30 :: Channels :== ([MTaskMSGRecv], [MTaskMSGSend], Bool)
31
32 :: SerTCP = SerialDevice | TCPDevice
33 :: MTaskDevice = {
34 deviceConnected :: Maybe String,
35 deviceName :: String
36 }
37
38 Start :: *World -> *World
39 Start world = startEngine (mTaskManager
40 >>* [OnAction (Action "Shutdown") (always $ shutDown)]) world
41
42 bc :: Main (ByteCode () Stmt)
43 bc = sds \x=1 In sds \pinnetje=1 In {main =
44 IF (digitalRead D3) (
45 x =. x +. lit 1 :.
46 pub x
47 ) (
48 noOp
49 ) :.
50 IF (pinnetje ==. lit 1) (
51 ledOn LED1
52 ) (
53 IF (pinnetje ==. lit 2) (
54 ledOn LED2
55 ) (
56 ledOn LED3
57 )
58 )}
59
60 bc2 :: UserLED -> Main (ByteCode () Stmt)
61 bc2 d = {main = ledOn d}
62
63 bc3 :: UserLED -> Main (ByteCode () Stmt)
64 bc3 d = {main = ledOff d}
65
66 :: MTaskDeviceStatus = {connected :: Bool, name :: String}
67 derive class iTask MTaskDeviceStatus, MTaskDevice
68
69 mTaskManager :: Task ()
70 mTaskManager = anyTask
71 [ viewmTasks @! ()
72 , viewShares
73 , whileUnchanged deviceStore viewDevices
74 ] <<@ ApplyLayout layout
75 where
76 isValue (Value _ _) = True
77 isValue _ = False
78
79 viewmTasks = enterChoice "Available mTasks" [ChooseFromList id] ["ledder", "ledon", "ledoff"]
80 >>= viewInformation "" []
81
82 layout = sequenceLayouts
83 [ arrangeWithSideBar 0 LeftSide 260 True
84 , arrangeSplit Vertical True
85 ]
86
87 viewShares :: Task ()
88 viewShares = viewInformation () [] ()
89
90 viewDevices :: [MTaskDevice] -> Task ()
91 viewDevices ds = anyTask [
92 addDevice deviceStore <<@ Title "Add new device" @! ():
93 [viewDevice d <<@ Title d.deviceName\\d<-ds]]
94 <<@ ArrangeWithTabs @! ()
95
96 viewDevice :: MTaskDevice -> Task ()
97 viewDevice d = (viewInformation "Device settings" [] d
98 ||- (case d.deviceConnected of
99 Just s = viewSharedInformation "Channels" [] (channels d.deviceName) @! ()
100 Nothing = viewInformation "No channels yet" [] "" @! ()
101 )) <<@ ArrangeHorizontal
102
103 channels :: String -> Shared Channels
104 channels s = sdsFocus s $ memoryStore "" $ Just ([], [], False)
105
106 addDevice :: (Shared [MTaskDevice]) -> Task ()
107 addDevice devices = enterInformation "Device type and name" []
108 >>= \(name, ty)->get randomInt @ ((+++) name o toString)
109 >>= \realname->let ch = channels realname in case ty of
110 TCPDevice = enterInformation "Hostname and port" []
111 >>= \(host, port)->cont realname name ||- syncNetworkChannel host port ch
112 SerialDevice = accWorld getDevices
113 >>= \dl->(enterChoice "Device" [] dl -&&- updateInformation "Settings" [] zero)
114 >>= \(device, settings)->cont realname name ||- syncSerialChannel device settings ch
115 where
116 cont rn nm = (upd (\l->[dev rn nm:l]) devices >>| addDevice devices)
117 dev rn nm = {deviceConnected=Just rn,deviceName=nm}
118
119 getDevices :: !*World -> *(![String], !*World)
120 getDevices w = case readDirectory "/dev" w of
121 (Error (errcode, errmsg), w) = abort errmsg
122 (Ok entries, w) = (map ((+++) "/dev/") (filter isTTY entries), w)
123
124 isTTY s = not (isEmpty (filter (flip startsWith s) prefixes))
125 prefixes = ["ttyS", "ttyACM", "ttyUSB", "tty.usbserial"]
126
127 // connectDevice :: [MTaskDevice] -> Task ()
128 // connectDevice [] = treturn ()
129 // connectDevice [d:ds] = (case d.deviceConnected of
130 // (Just sh) = viewSharedInformation "Buffers" [] sh @! ()
131 // Nothing = viewInformation ("Connect " +++ d.deviceName) [] "" >>* [
132 // OnAction (Action "connect") (const $ Just $ connect d)]
133 // ) -|| connectDevice ds
134
135 deviceviewer :: [MTaskDevice] -> [MTaskDeviceStatus]
136 deviceviewer ds = [{MTaskDeviceStatus | name = d.deviceName,
137 connected = if (isNothing d.deviceConnected) False True}\\d<-ds]
138
139 deviceStore :: Shared [MTaskDevice]
140 deviceStore = sdsFocus "mTaskDevices" $ memoryStore "" (Just [])
141
142 // showTabbed :: [MTaskDevice] -> Task ()
143 // showTabbed [] = viewInformation "" [] "No devices yet" @! ()
144 // showTabbed [l:ls] = foldr (\e es->manageDevice e ||- es) (manageDevice l) ls
145 //
146 // manageDevice :: MTaskDevice -> Task ()
147 // manageDevice md =
148 // either viewTCP viewSer md.deviceSettings
149 // ||- maybe
150 // (treturn () >>* [OnAction (Action "Connect") (always shutDown)] @! ())
151 // (\b->viewSharedInformation "Buffers" [] b @! ())
152 // md.deviceConnected
153 // <<@ ArrangeVertical
154
155 mapPar :: (a -> Task a) [a] -> Task ()
156 mapPar f l = foldr1 (\x y->f x ||- y) l <<@ ArrangeWithTabs @! ()
157 allAtOnce t = foldr1 (||-) t @! ()
158 //allAtOnce = (flip (@!) ()) o foldr1 (||-)
159
160
161 //mTaskTask :: Task ()
162 //mTaskTask = let (msgs, sdsShares) = makeMsgs 1000 bc in
163 // withDevice \ch->
164 // sendMsg msgs ch
165 // ||- processMessages ch messageShare sdsShares
166 // ||- forever (enterChoice "Choose led to enable" [] [LED1, LED2, LED3]
167 // >>= \p->sendMsg (fst (makeMsgs 0 (bc2 p))) ch)
168 // ||- forever (enterChoice "Choose led to disable" [] [LED1, LED2, LED3]
169 // >>= \p->sendMsg (fst (makeMsgs 0 (bc3 p))) ch)
170 // ||- viewSharedInformation "channels" [ViewAs lens] ch
171 // ||- viewSharedInformation "messages" [] messageShare
172 // ||- viewSh sdsShares ch
173 // >>* [OnAction ActionFinish (always shutDown)]
174 // where
175 // messageShare :: Shared [String]
176 // messageShare = sharedStore "mTaskMessagesRecv" []
177 //
178 // processMessages ch msgs sdss = forever (watch ch
179 // >>* [OnValue (ifValue (not o isEmpty o fst3) (process ch))])
180 // where
181 // process :: (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> Task ()
182 // process ch (r,_,_) = upd (appFst3 (const [])) ch >>| process` r
183 // where
184 // process` = foldr (\r t->updateSDSs sdss msgs r >>| t) (return ())
185 //
186 // makeMsgs :: Int (Main (ByteCode () Stmt)) -> ([MTaskMSGSend], [(Int, Shared Int)])
187 // makeMsgs timeout bc
188 // # (msgs, st) = toMessages timeout (toRealByteCode (unMain bc))
189 // = (msgs, map f st.sdss)
190 // where
191 // f (i,d) = (i, sharedStore ("mTaskSDS-" +++ toString i) (dd d))
192 // dd [x,y] = toInt x*265 + toInt y
193 //
194 // updateSDSs :: [(Int, Shared Int)] (Shared [String]) MTaskMSGRecv -> Task ()
195 // updateSDSs [(id, sh):xs] m n=:(MTPub i d)
196 // | id == i = set ((toInt d.[0])*265 + toInt d.[1]) sh @! ()
197 // = updateSDSs xs m n
198 // updateSDSs _ m mtm = case mtm of
199 // MTMessage s = upd (\l->take 5 [s:l]) m @! ()
200 // mta=:(MTTaskAck _) = upd (\l->take 5 [toString mta:l]) m @! ()
201 // //TODO other recv msgs
202 // _ = return ()
203 //
204 // lens :: ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> ([String], [String])
205 // lens (r,s,_) = (map toString r, map toString s)
206 //
207 // viewSh :: [(Int, Shared Int)] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
208 // viewSh [] ch = return ()
209 // viewSh [(i, sh):xs] ch
210 // # sharename = "SDS-" +++ toString i
211 // = (
212 // viewSharedInformation ("SDS-" +++ toString i) [] sh ||-
213 // forever (
214 // enterInformation sharename []
215 // >>* [OnAction ActionOk
216 // (ifValue (\j->j>=1 && j <= 3)
217 // (\c->set c sh
218 // >>= \_->sendMsg (toSDSUpdate i c) ch
219 // @! ()
220 // )
221 // )]
222 // )
223 // ) ||- viewSh xs ch
224
225 sendMsg :: [MTaskMSGSend] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
226 sendMsg m ch = upd (\(r,s,ss)->(r,s ++ m,True)) ch @! ()
227
228 syncSerialChannel :: String TTYSettings (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
229 syncSerialChannel dev opts rw = Task eval
230 where
231 eval event evalOpts tree=:(TCInit taskId ts) iworld=:{IWorld|world}
232 = case TTYopen dev opts world of
233 (False, _, world)
234 # (err, world) = TTYerror world
235 = (ExceptionResult (exception err), {iworld & world=world})
236 (True, tty, world)
237 # iworld = {iworld & world=world, resources=Just (TTYd tty)}
238 = case addBackgroundTask 42 (BackgroundTask (serialDeviceBackgroundTask rw)) iworld of
239 (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
240 (Ok _, iworld) = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=True} NoChange (TCBasic taskId ts JSONNull False), iworld)
241
242 eval _ _ tree=:(TCBasic _ ts _ _) iworld
243 = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=False} NoChange tree, iworld)
244
245 eval event evalOpts tree=:(TCDestroy _) iworld=:{IWorld|resources,world}
246 # (TTYd tty) = fromJust resources
247 # (ok, world) = TTYclose tty world
248 # iworld = {iworld & world=world,resources=Nothing}
249 = case removeBackgroundTask 42 iworld of
250 (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
251 (Ok _, iworld) = (DestroyedResult, iworld)
252
253 serialDeviceBackgroundTask :: (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) !*IWorld -> (MaybeError TaskException (), *IWorld)
254 serialDeviceBackgroundTask rw iworld
255 = case read rw iworld of
256 (Error e, iworld) = (Error $ exception "share couldn't be read", iworld)
257 (Ok (r,s,ss), iworld)
258 # (Just (TTYd tty)) = iworld.resources
259 # tty = writet (map encode s) tty
260 # (ml, tty) = case TTYavailable tty of
261 (False, tty) = ([], tty)
262 (_, tty)
263 # (l, tty) = TTYreadline tty
264 = ([decode l], tty)
265 # iworld = {iworld & resources=Just (TTYd tty)}
266 = case write (r++ml,[],False) rw iworld of
267 (Error e, iworld) = (Error $ exception "share couldn't be written", iworld)
268 (Ok _, iworld) = case notify rw iworld of
269 (Error e, iworld) = (Error $ exception "share couldn't be notified", iworld)
270 (Ok _, iworld) = (Ok (), iworld)
271 where
272 writet :: [String] -> (*TTY -> *TTY)
273 writet [] = id
274 writet [x:xs] = writet xs o TTYwrite x
275
276
277 syncNetworkChannel :: String Int (Shared ([MTaskMSGRecv], [MTaskMSGSend], Bool)) -> Task ()
278 syncNetworkChannel server port channel
279 = tcpconnect server port channel {ConnectionHandlers|onConnect=onConnect,whileConnected=whileConnected,onDisconnect=onDisconnect} @! ()
280 where
281 onConnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
282 onConnect _ (msgs,send,sendStopped)
283 = (Ok "", Just (msgs,[],sendStopped), map encode send, False)
284
285 whileConnected :: (Maybe String) String ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
286 whileConnected Nothing acc (msgs,send,sendStopped)
287 = (Ok acc, Nothing, [], False)
288
289 whileConnected (Just newData) acc (msgs,send,sendStopped)
290 | sendStopped = (Ok acc, Just (msgs ++ [decode newData],[],False), map encode send, False)
291 = (Ok acc, Just (msgs ++ [decode newData],[],False), [], False)
292
293 onDisconnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool))
294 onDisconnect l (msgs,send,sendStopped) = (Ok l, Nothing)