clean up, move iTasks serial stuff to Cleanserial, add toplevel tasks for syncing
[mTask.git] / miTask.icl
index e81f47d..a20108c 100644 (file)
@@ -8,8 +8,11 @@ import mTask
 
 from Text import class Text(startsWith,concat,split,join), instance Text String
 
 
 from Text import class Text(startsWith,concat,split,join), instance Text String
 
+import qualified Data.Map as DM
+
 from Data.Func import $
 import Data.Tuple
 from Data.Func import $
 import Data.Tuple
+import Data.List
 import System.Directory
 
 import iTasks.UI.Definition
 import System.Directory
 
 import iTasks.UI.Definition
@@ -19,21 +22,50 @@ import iTasks._Framework.TaskServer
 import iTasks._Framework.IWorld
 import iTasks._Framework.Store
 
 import iTasks._Framework.IWorld
 import iTasks._Framework.Store
 
-import TTY
+
+import TTY, iTasksTTY
 
 derive class iTask Queue, TTYSettings, Parity, BaudRate, ByteSize
 derive class iTask MTaskMSGRecv, MTaskMSGSend, SerTCP, UserLED
 
 
 derive class iTask Queue, TTYSettings, Parity, BaudRate, ByteSize
 derive class iTask MTaskMSGRecv, MTaskMSGSend, SerTCP, UserLED
 
-derive class iTask MTaskDevice
-
-:: SerTCP = Serial | TCP
 :: *Resource | TTYd !*TTY
 :: *Resource | TTYd !*TTY
-:: MTaskDevice = SerialDevice String TTYSettings | TCPDevice String Int
+:: Channels :== ([MTaskMSGRecv], [MTaskMSGSend], Bool)
+
+:: SerTCP = SerialDevice | TCPDevice
+:: MTaskDevice = {
+               deviceTask :: Maybe TaskId,
+               deviceConnected :: Maybe String,
+               deviceName :: String,
+               deviceTasks :: [(String, Int)]
+       }
+:: MTaskShare = {
+               initValue :: Int,
+               withTask :: String,
+               identifier :: Int,
+               realShare :: String
+       }
 
 Start :: *World -> *World
 Start world = startEngine (mTaskManager
        >>* [OnAction (Action "Shutdown") (always $ shutDown)]) world
 
 Start :: *World -> *World
 Start world = startEngine (mTaskManager
        >>* [OnAction (Action "Shutdown") (always $ shutDown)]) world
-//Start world = startEngine mTaskTask world
+
+memoryShare :: String a -> Shared a | iTask a
+memoryShare s d = sdsFocus s $ memoryStore "" $ Just d
+
+deviceStore :: Shared [MTaskDevice]
+deviceStore = memoryShare "mTaskDevices" []
+
+sdsStore :: Shared [MTaskShare]
+sdsStore = memoryShare "mTaskShares" []
+
+bcStateStore :: Shared BCState
+bcStateStore = memoryShare "mTaskBCState" zero
+
+mTaskTaskStore :: Shared [String]
+mTaskTaskStore = memoryShare "mTaskTasks" ["ledder", "ledon", "ledoff"]
+
+mTaskMap :: Map String (Main (ByteCode () Stmt))
+mTaskMap = 'DM'.fromList [("ledder", bc), ("ledon", bc2 LED1), ("ledoff", bc3 LED3)]
 
 bc :: Main (ByteCode () Stmt)
 bc = sds \x=1 In sds \pinnetje=1 In {main =
 
 bc :: Main (ByteCode () Stmt)
 bc = sds \x=1 In sds \pinnetje=1 In {main =
@@ -59,111 +91,204 @@ bc2 d = {main = ledOn d}
 bc3 :: UserLED -> Main (ByteCode () Stmt)
 bc3 d = {main = ledOff d}
 
 bc3 :: UserLED -> Main (ByteCode () Stmt)
 bc3 d = {main = ledOff d}
 
-withDevice :: ((Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task a) -> Task a | iTask a
-withDevice t = withShared ([], [], False) \ch->
-               enterInformation "Type" []
-       >>= \ty->case ty of
-               TCP = (enterInformation "Host" [] -&&- enterInformation "Port" [])
-                       >>= \(port,host)->t ch -|| syncNetworkChannel host port ch
-               Serial = accWorld getDevices
-                       >>= \dl->(enterChoice "Device" [] dl -&&- updateInformation "Settings" [] zero)
-                       >>= \(dev,set)->t ch -|| syncSerialChannel dev set ch
-       where
-               getDevices :: !*World -> *(![String], !*World)
-               getDevices w = case readDirectory "/dev" w of
-                       (Error (errcode, errmsg), w) = abort errmsg
-                       (Ok entries, w) = (map ((+++) "/dev/") (filter isTTY entries), w)
-                       where
-                               isTTY s = not (isEmpty (filter (flip startsWith s) prefixes))
-                               prefixes = ["ttyS", "ttyACM", "ttyUSB", "tty.usbserial"]
+:: MTaskDeviceStatus = {connected :: Bool, name :: String, tasks :: [(String, Int)]}
+derive class iTask MTaskDeviceStatus, MTaskDevice, MTaskShare, BCState
 
 mTaskManager :: Task ()
 
 mTaskManager :: Task ()
-mTaskManager = viewSharedInformation "Devices" [] deviceStore
-       ||- forever (addDevice >>= \d->upd (\l->[d:l]) deviceStore) @! ()
-       where
-               deviceStore :: Shared [MTaskDevice]
-               deviceStore = sdsFocus "mTaskDevices" $ memoryStore "" (Just [])
-
-addDevice :: Task MTaskDevice
-addDevice = enterInformation "Enter device type" []
-       >>= \ty->case ty of
-               TCP = (enterInformation "Host" [] -&&- enterInformation "Port" [])
-                       >>= return o uncurry TCPDevice
-               Serial = accWorld getDevices
-                       >>= \dl->(enterChoice "Device" [] dl -&&- updateInformation "Settings" [] zero)
-                       >>= return o uncurry SerialDevice
+mTaskManager = anyTask 
+               [ viewmTasks @! ()
+               , viewShares
+               , whileUnchanged deviceStore viewDevices
+               ] <<@ ApplyLayout layout
        where
        where
-               getDevices :: !*World -> *(![String], !*World)
-               getDevices w = case readDirectory "/dev" w of
-                       (Error (errcode, errmsg), w) = abort errmsg
-                       (Ok entries, w) = (map ((+++) "/dev/") (filter isTTY entries), w)
+               layout = sequenceLayouts
+                       [ arrangeWithSideBar 0 LeftSide 260 True
+                       , arrangeSplit Vertical True
+                       ]
+
+               viewmTasks = listmTasks
+                       >&^ \sh->whileUnchanged sh $ \mi->case mi of
+                               Nothing = viewInformation "No task selected" [] ()
+                               Just mTaskTask = get deviceStore
+                                       >>= \devices->case devices of
+                                               [] = viewInformation "No devices yet" [] ()
+                                               ds = sendmTask mTaskTask ds @! ()
                        where
                        where
-                               isTTY s = not (isEmpty (filter (flip startsWith s) prefixes))
-                               prefixes = ["ttyS", "ttyACM", "ttyUSB", "tty.usbserial"]
-
-mTaskTask :: Task ()
-mTaskTask = let (msgs, sdsShares) = makeMsgs 1000 bc in
-       withDevice \ch->
-                       sendMsg msgs ch
-               ||- processMessages ch messageShare sdsShares
-               ||- forever (enterChoice "Choose led to enable" [] [LED1, LED2, LED3]
-                               >>= \p->sendMsg (fst (makeMsgs 0 (bc2 p))) ch)
-               ||- forever (enterChoice "Choose led to disable" [] [LED1, LED2, LED3]
-                               >>= \p->sendMsg (fst (makeMsgs 0 (bc3 p))) ch)
-               ||- viewSharedInformation "channels" [ViewAs lens] ch
-               ||- viewSharedInformation "messages" [] messageShare
-               ||- viewSh sdsShares ch
-               >>* [OnAction ActionFinish (always shutDown)]
-       where
-               messageShare :: Shared [String]
-               messageShare = sharedStore "mTaskMessagesRecv" []
-
-               processMessages ch msgs sdss = forever (watch ch
-                       >>* [OnValue (ifValue (not o isEmpty o fst3) (process ch))])
-                       where
-                               process :: (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> Task ()
-                               process ch (r,_,_) = upd (appFst3 (const [])) ch >>| process` r
+                               listmTasks :: Task String
+                               listmTasks = enterChoiceWithShared "Available mTasks" [ChooseFromList id] mTaskTaskStore
+
+                               sendmTask mTaskId ds = 
+                                               (enterChoice "Choose Device" [ChooseFromDropdown \t->t.deviceName] ds
+                                               -&&- enterInformation "Timeout, 0 for one-shot" [])
+                                       >>* [OnAction (Action "Send") (withValue $ Just o sendToDevice mTaskId)]
+
+                               sendToDevice :: String (MTaskDevice, Int) -> Task ()
+                               sendToDevice mTask (device, timeout) =
+                                               get bcStateStore @ createBytecode
+                                       >>= \(msgs, st1)->set st1 bcStateStore @ toSDSRecords
+                                       >>= \sdss->upd ((++)sdss) sdsStore//MTaskShareaddToSDSShare
+                                       >>| makeShares sdss
+                                       >>| upd (\(r,s,ss)->(r,s++msgs,ss)) (channels device)
+                                       @! ()
                                        where
                                        where
-                                               process` = foldr (\r t->updateSDSs sdss msgs r >>| t) (return ())
-
-               makeMsgs :: Int (Main (ByteCode () Stmt)) -> ([MTaskMSGSend], [(Int, Shared Int)])
-               makeMsgs timeout bc
-               # (msgs, st) = toMessages timeout (toRealByteCode (unMain bc))
-               = (msgs, map f st.sdss)
-                       where 
-                               f (i,d) = (i, sharedStore ("mTaskSDS-" +++ toString i) (dd d))
-                               dd [x,y] = toInt x*265 + toInt y
-
-               updateSDSs :: [(Int, Shared Int)] (Shared [String]) MTaskMSGRecv -> Task ()
-               updateSDSs [(id, sh):xs] m n=:(MTPub i d)
-               | id == i = set ((toInt d.[0])*265 + toInt d.[1]) sh @! ()
-               = updateSDSs xs m n
-               updateSDSs _ m mtm = case mtm of
-                       MTMessage s = upd (\l->take 5 [s:l]) m @! ()
-                       mta=:(MTTaskAck _) = upd (\l->take 5 [toString mta:l]) m @! ()
-                       //TODO other recv msgs
-                       _ = return ()
-
-               lens :: ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> ([String], [String])
-               lens (r,s,_) = (map toString r, map toString s)
-
-               viewSh :: [(Int, Shared Int)] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
-               viewSh [] ch = return ()
-               viewSh [(i, sh):xs] ch
-               # sharename = "SDS-" +++ toString i
-               = (
-                               viewSharedInformation ("SDS-" +++ toString i) [] sh ||-
-                               forever (
-                                       enterInformation sharename []
-                                       >>* [OnAction ActionOk 
-                                                       (ifValue (\j->j>=1 && j <= 3) 
-                                                       (\c->set c sh
-                                                               >>= \_->sendMsg (toSDSUpdate i c) ch
-                                                               @! ()
-                                                       )
-                                               )]
-                               )
-                       ) ||- viewSh xs ch
+                                               createBytecode st = toMessages timeout $ toRealByteCode (unMain $ fromJust ('DM'.get mTask mTaskMap)) st
+                                               sharename i = fromJust (device.deviceConnected) +++ "-" +++ toString i
+                                               toSDSRecords st = [{MTaskShare |
+                                                       initValue=toInt d1*265 + toInt d2,
+                                                       withTask=mTask,
+                                                       identifier=i,
+                                                       realShare="mTaskSDS-" +++ toString i}
+                                                               \\(i,[d1,d2])<-st.sdss]
+                                               makeShares = foldr (\sh t->set sh.initValue (getSDSStore sh) >>| t) (treturn ())
+                                       
+               getSDSStore :: MTaskShare -> Shared Int
+               getSDSStore sh = memoryShare sh.realShare 0
+                                       
+               channels :: MTaskDevice -> Shared Channels
+               channels d = memoryShare (fromJust d.deviceConnected) ([], [], False)
+
+               viewShares :: Task ()
+               viewShares = forever $ viewSharedInformation "Shares" [] sdsStore @! ()
+//                             enterChoiceWithShared "Shares" [ChooseFromList id] sdsStore
+//                     >>* [OnValue $ withValue $ Just o updateShare]
+//                     >>* [OnAction (Action "Back") (const $ Just $ treturn ())]
+//                     where
+//                             sdsvw (k, v) = concat ["SDS ", toString k, ": ", toString v]
+//                             updateShare s = viewInformation "" [] ()
+//                             updateShare (k, v) = (viewInformation "Key" [] k
+//                                     ||- updateInformation "Value" [] v)
+                                       
+
+               viewDevices :: [MTaskDevice] -> Task ()
+               viewDevices ds = anyTask [
+                               addDevice deviceStore <<@ Title "Add new device" @! ():
+                                       [viewDevice d <<@ Title d.deviceName\\d<-ds]]
+                       <<@ ArrangeWithTabs @! ()
+               
+               viewDevice :: MTaskDevice -> Task ()
+               viewDevice d = (viewInformation "Device settings" [] d 
+                               ||- (case d.deviceConnected of
+                                       Just s = viewSharedInformation "Channels" [ViewAs dropEmpty] (channels d) @! ()
+                                       Nothing = viewInformation "No channels yet" [] "" @! ()
+                               )) <<@ ArrangeHorizontal
+                       where
+                               dropEmpty (r,s,ss) = (filter ((=!=)MTEmpty) r,s,ss)
+
+               addDevice :: (Shared [MTaskDevice]) -> Task SerTCP
+               addDevice devices = enterInformation "Device type" []
+                       >&^ \sh->whileUnchanged sh $ \mty->case mty of
+                               Nothing = viewInformation "No type selected yet" [] "" @! ()
+                               Just ty = case ty of
+                                       TCPDevice = (enterInformation "Name" [] -&&- enterInformation "Hostname" [] -&&- enterInformation "Port" [])
+                                               >>= \(name, (host, port))->cont name (syncNetworkChannel host port)
+                                       SerialDevice = accWorld getTTYDevices
+                                               >>= \dl->(enterInformation "Name" [] -&&- enterChoice "Device" [] dl -&&- updateInformation "Settings" [] zero)
+                                               >>= \(name, (dev, set))->cont name (syncSerialChannel dev set)
+                       where
+                               cont :: String ((Shared Channels) -> Task ()) -> Task ()
+                               cont name synfun = get randomInt 
+                                       @ (\randint->{deviceConnected=Just (name +++ toString randint), deviceName=name, deviceTasks=[], deviceTask=Nothing})
+                                       >>= \dev->appendTopLevelTask 'DM'.newMap True (synfun $ channels dev)
+                                       >>= \tid->upd (\l->[{dev & deviceTask=Just tid}:l]) devices
+                                       @! ()
+                                               
+//                             >= \ty->get randomInt @ (\randint->{deviceConnected=Just (name +++ toString randint), deviceName=name, deviceTasks=[]})
+//                     >>= \dev->let ch = channels dev in case ty of
+//                             TCPDevice = enterInformation "Hostname and port" []
+//                                     >>= \(host, port)->cont dev ||- syncNetworkChannel host port ch
+//                             SerialDevice = accWorld getDevices
+//                                     >>= \dl->(enterChoice "Device" [] dl -&&- updateInformation "Settings" [] zero)
+//                                     >>= \(device, settings)->cont dev ||- syncSerialChannel device settings ch
+//                     where
+//                             cont d = (upd (\l->[d:l]) devices >>| addDevice devices)
+
+//             connectDevice :: [MTaskDevice] -> Task ()
+//             connectDevice [] = treturn ()
+//             connectDevice [d:ds] = (case d.deviceConnected of
+//                     (Just sh) = viewSharedInformation "Buffers" [] sh @! ()
+//                     Nothing = viewInformation ("Connect " +++ d.deviceName) [] "" >>* [
+//                             OnAction (Action "connect") (const $ Just $ connect d)]
+//                     ) -|| connectDevice ds
+
+               deviceviewer :: [MTaskDevice] -> [MTaskDeviceStatus]
+               deviceviewer ds = [{MTaskDeviceStatus | name = d.deviceName,
+                       connected = if (isNothing d.deviceConnected) False True,
+                       tasks = d.deviceTasks}\\d<-ds]
+       
+//             showTabbed :: [MTaskDevice] -> Task ()
+//             showTabbed [] = viewInformation "" [] "No devices yet" @! ()
+//             showTabbed [l:ls] = foldr (\e es->manageDevice e ||- es) (manageDevice l) ls
+//
+//             manageDevice :: MTaskDevice -> Task ()
+//             manageDevice md = 
+//                             either viewTCP viewSer md.deviceSettings
+//                     ||- maybe
+//                             (treturn () >>* [OnAction (Action "Connect") (always shutDown)] @! ())
+//                             (\b->viewSharedInformation "Buffers" [] b @! ())
+//                             md.deviceConnected
+//                     <<@ ArrangeVertical
+
+               mapPar :: (a -> Task a) [a] -> Task ()
+               mapPar f l = foldr1 (\x y->f x ||- y) l <<@ ArrangeWithTabs @! ()
+               allAtOnce t = foldr1 (||-) t @! ()
+               //allAtOnce = (flip (@!) ()) o foldr1 (||-)
+
+
+//mTaskTask :: Task ()
+//mTaskTask = let (msgs, sdsShares) = makeMsgs 1000 bc in
+//     withDevice \ch->
+//                     sendMsg msgs ch
+//             ||- processMessages ch messageShare sdsShares
+//             ||- forever (enterChoice "Choose led to enable" [] [LED1, LED2, LED3]
+//                             >>= \p->sendMsg (fst (makeMsgs 0 (bc2 p))) ch)
+//             ||- forever (enterChoice "Choose led to disable" [] [LED1, LED2, LED3]
+//                             >>= \p->sendMsg (fst (makeMsgs 0 (bc3 p))) ch)
+//             ||- viewSharedInformation "channels" [ViewAs lens] ch
+//             ||- viewSharedInformation "messages" [] messageShare
+//             ||- viewSh sdsShares ch
+//             >>* [OnAction ActionFinish (always shutDown)]
+//     where
+//             messageShare :: Shared [String]
+//             messageShare = sharedStore "mTaskMessagesRecv" []
+//
+//             makeMsgs :: Int (Main (ByteCode () Stmt)) -> ([MTaskMSGSend], [(Int, Shared Int)])
+//             makeMsgs timeout bc
+//             # (msgs, st) = toMessages timeout (toRealByteCode (unMain bc))
+//             = (msgs, map f st.sdss)
+//                     where 
+//                             f (i,d) = (i, sharedStore ("mTaskSDS-" +++ toString i) (dd d))
+//                             dd [x,y] = toInt x*265 + toInt y
+//
+//             updateSDSs :: [(Int, Shared Int)] (Shared [String]) MTaskMSGRecv -> Task ()
+//             updateSDSs [(id, sh):xs] m n=:(MTPub i d)
+//             | id == i = set ((toInt d.[0])*265 + toInt d.[1]) sh @! ()
+//             = updateSDSs xs m n
+//             updateSDSs _ m mtm = case mtm of
+//                     MTMessage s = upd (\l->take 5 [s:l]) m @! ()
+//                     mta=:(MTTaskAck _) = upd (\l->take 5 [toString mta:l]) m @! ()
+//                     //TODO other recv msgs
+//                     _ = return ()
+//
+//             lens :: ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> ([String], [String])
+//             lens (r,s,_) = (map toString r, map toString s)
+//
+//             viewSh :: [(Int, Shared Int)] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
+//             viewSh [] ch = return ()
+//             viewSh [(i, sh):xs] ch
+//             # sharename = "SDS-" +++ toString i
+//             = (
+//                             viewSharedInformation ("SDS-" +++ toString i) [] sh ||-
+//                             forever (
+//                                     enterInformation sharename []
+//                                     >>* [OnAction ActionOk 
+//                                                     (ifValue (\j->j>=1 && j <= 3) 
+//                                                     (\c->set c sh
+//                                                             >>= \_->sendMsg (toSDSUpdate i c) ch
+//                                                             @! ()
+//                                                     )
+//                                             )]
+//                             )
+//                     ) ||- viewSh xs ch
 
 sendMsg :: [MTaskMSGSend] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
 sendMsg m ch = upd (\(r,s,ss)->(r,s ++ m,True)) ch @! ()
 
 sendMsg :: [MTaskMSGSend] (Shared ([MTaskMSGRecv],[MTaskMSGSend],Bool)) -> Task ()
 sendMsg m ch = upd (\(r,s,ss)->(r,s ++ m,True)) ch @! ()
@@ -218,8 +343,9 @@ serialDeviceBackgroundTask rw iworld
 
 
 syncNetworkChannel :: String Int (Shared ([MTaskMSGRecv], [MTaskMSGSend], Bool)) -> Task ()
 
 
 syncNetworkChannel :: String Int (Shared ([MTaskMSGRecv], [MTaskMSGSend], Bool)) -> Task ()
-syncNetworkChannel server port channel
-       = tcpconnect server port channel {ConnectionHandlers|onConnect=onConnect,whileConnected=whileConnected,onDisconnect=onDisconnect} @! ()
+syncNetworkChannel server port channel = catchAll
+               (tcpconnect server port channel {ConnectionHandlers|onConnect=onConnect,whileConnected=whileConnected,onDisconnect=onDisconnect} @! ())
+               (\v->traceValue v @! ())
        where
                onConnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
                onConnect _ (msgs,send,sendStopped)
        where
                onConnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
                onConnect _ (msgs,send,sendStopped)
@@ -228,11 +354,11 @@ syncNetworkChannel server port channel
                whileConnected :: (Maybe String) String ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
                whileConnected Nothing acc (msgs,send,sendStopped)
                = (Ok acc, Nothing, [], False)
                whileConnected :: (Maybe String) String ([MTaskMSGRecv], [MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool), [String], Bool)
                whileConnected Nothing acc (msgs,send,sendStopped)
                = (Ok acc, Nothing, [], False)
-//             = (Ok acc, Just (msgs,[],sendStopped), map encode send, False)
 
                whileConnected (Just newData) acc (msgs,send,sendStopped)
 
                whileConnected (Just newData) acc (msgs,send,sendStopped)
-               | sendStopped = (Ok acc, Just (msgs ++ [decode newData],[],False), map encode send, False)
-               = (Ok acc, Just (msgs ++ [decode newData],[],False), [], False)
+               = (Ok acc, Just (msgs ++ [decode newData],[],False), map encode send, False)
+               //| sendStopped = (Ok acc, Just (msgs ++ [decode newData],[],False), map encode send, False)
+//             = (Ok acc, Just (msgs ++ [decode newData],[],False), [], False)
                
                onDisconnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool))
                onDisconnect l (msgs,send,sendStopped) = (Ok l, Nothing)
                
                onDisconnect :: String ([MTaskMSGRecv],[MTaskMSGSend],Bool) -> (MaybeErrorString String, Maybe ([MTaskMSGRecv],[MTaskMSGSend],Bool))
                onDisconnect l (msgs,send,sendStopped) = (Ok l, Nothing)