not working again.
[mTask.git] / miTask.icl
index e5483cc..5df0450 100644 (file)
@@ -1,37 +1,70 @@
 module miTask
 
 import StdDebug, StdMisc
-
-from Text import class Text(concat,join,split), instance Text String
+from StdFunc import flip
 
 import iTasks
 import mTask
 
+from Text import class Text(startsWith,concat,split,join), instance Text String
+
+import Data.Tuple
+import System.Directory
+
+import iTasks.UI.Definition
+
+import iTasks._Framework.TaskState
+import iTasks._Framework.TaskServer
+import iTasks._Framework.IWorld
+import iTasks._Framework.Store
+
+import TTY
+
+derive class iTask Queue, TTYSettings, Parity, BaudRate, ByteSize
 derive class iTask MTaskMSGRecv, MTaskMSGSend
 
+:: *Resource | TTYd !*TTY
+
 Start :: *World -> *World
-Start world = startEngine (
-       enterInformation "Port Number?" []
-       >>= \port->withShared ([], False, [], False) (mTaskTask port)
-       ) world
+Start world = startEngine (withShared ([], False, [], False) mTaskTask) world
 //Start world = startEngine mTaskTask world
+//
+deviceSelectorNetwork :: Task (Int, String)
+deviceSelectorNetwork = enterInformation "Port Number?" []
+       -&&- enterInformation "Network address" []
+
+deviceSelectorSerial :: Task (String, TTYSettings)
+deviceSelectorSerial = accWorld getDevices
+       >>= \dl->(enterChoice "Device" [] dl -&&- deviceSettings)
+       where
+               deviceSettings = updateInformation "Settings" [] zero
 
-mTaskTask :: Int (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
-mTaskTask port ch =
-       syncNetworkChannel "localhost" port "\n" decode encode` ch ||-
-       sendMsg msgs ch ||-
+               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"]
+
+derive class iTask SerTCP
+:: SerTCP = Serial | TCP
+
+mTaskTask :: (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
+mTaskTask ch = 
+       (enterInformation "Choose" [] >>= \st->case st of
+               Serial = deviceSelectorSerial >>= \(s,set)->syncSerialChannel s set decode encode ch
+               TCP = deviceSelectorNetwork >>= \(p,h)->syncNetworkChannel h p "\n" decode encode ch
+       ) ||-
        (
-               (
+               sendMsg msgs ch >>= \_->(
                        consumeNetworkStream (processSDSs sdsShares messageShare) ch ||-
                        viewSharedInformation "channels" [ViewWith lens] ch ||-
+                       viewSharedInformation "messages" [] messageShare ||-
                        viewSh sdsShares ch
-               ) >>* [OnAction ActionFinish (always shutDown)]
-       )
+               )
+       ) >>* [OnAction ActionFinish (always shutDown)]
        where
-               encode` m
-               | not (trace_tn (toString (toJSON m))) = undef
-               = encode m
-
                messageShare :: Shared [String]
                messageShare = sharedStore "mTaskMessagesRecv" []
 
@@ -40,7 +73,7 @@ mTaskTask port ch =
                processSDSs s y [x:xs] = updateSDSs s y x >>= \_->processSDSs s y xs
 
                updateSDSs :: [(Int, Shared Int)] (Shared [String]) MTaskMSGRecv -> Task ()
-               updateSDSs _ m (MTMessage s) = upd (\l->[s:l]) m @! ()
+               updateSDSs _ m (MTMessage s) = upd (\l->take 20 [s:l]) m @! ()
                updateSDSs _ _ MTEmpty = return ()
                updateSDSs [(id, sh):xs] m n=:(MTPub i d)
                | id == i = set ((toInt d.[0])*265 + toInt d.[1]) sh @! ()
@@ -72,42 +105,99 @@ mTaskTask port ch =
                        ) ||- viewSh xs ch
 
                sdsShares = makeShares st
-
-               (msgs, st) = toMessages 500 (toRealByteCode (unMain bc))
+               (msgs, st) = toMessages 1000 (toRealByteCode (unMain bc))
 
                bc :: Main (ByteCode () Stmt)
                bc = sds \x=1 In sds \pinnetje=1 In {main =
-                               x =. x +. lit 1 :.
-                               pub x :.
+                               IF (digitalRead D3 ==. lit True) (
+                                       x =. x +. lit 1 :.
+                                       pub x
+                               ) (
+                                       noOp
+                               ) :.
                                IF (pinnetje ==. lit 1) (
-                                       analogWrite A0 (lit 1) :.
-                                       analogWrite A1 (lit 0) :.
-                                       analogWrite A2 (lit 0)
+                                       digitalWrite D0 (lit True) :.
+                                       digitalWrite D1 (lit False) :.
+                                       digitalWrite D2 (lit False)
                                ) (
                                        IF (pinnetje ==. lit 2) (
-                                               analogWrite A0 (lit 0) :.
-                                               analogWrite A1 (lit 1) :.
-                                               analogWrite A2 (lit 0)
+                                               digitalWrite D0 (lit False) :.
+                                               digitalWrite D1 (lit True) :.
+                                               digitalWrite D2 (lit False)
                                        ) (
-                                               analogWrite A0 (lit 0):.
-                                               analogWrite A1 (lit 0):.
-                                               analogWrite A2 (lit 1)
+                                               digitalWrite D0 (lit False) :.
+                                               digitalWrite D1 (lit False) :.
+                                               digitalWrite D2 (lit True)
                                        )
                                )}
-//             bc :: Main (ByteCode Int Stmt)
-//             bc = sds \x=1 In {main =
-//                     If (x ==. lit 3)
-//                     (x =. lit 1)
-//                     (x =. x +. lit 1) :. pub x}
 
 makeShares :: BCState -> [(Int, Shared Int)]
 makeShares {sdss=[]} = []
 makeShares s=:{sdss=[(i,d):xs]} =
-       [(i, sharedStore ("mTaskSDS-" +++ toString i) 0):makeShares {s & sdss=xs}]
+       [(i, sharedStore ("mTaskSDS-" +++ toString i) 1):makeShares {s & sdss=xs}]
+
+//makeBytecode :: Int (Main (ByteCode () Stmt)) -> ([MTaskMSGSend], [(Int, Shared Int)])
+//makeBytecode timeout bc
+//# (msgs, st) = toMessages timeout (toRealByteCode (unMain bc))
+//# shares = map (\(i,d)->(i, sharedStore (s i) (dd d))) st.sdss
+//= (msgs, shares)
+//     where
+//             s i = "mTaskSDS-" +++ toString i
+//             dd [x,y] = (toInt x)*265+(toInt y)
+       
 
 sendMsg :: [MTaskMSGSend] (Shared ([MTaskMSGRecv],Bool,[MTaskMSGSend],Bool)) -> Task ()
 sendMsg m ch = upd (\(r,rs,s,ss)->(r,rs,s ++ m,ss)) ch @! ()
 
+syncSerialChannel :: String TTYSettings (String -> m) (n -> String) (Shared ([m],Bool,[n],Bool)) -> Task () | iTask m & iTask n
+syncSerialChannel dev opts decodeFun encodeFun rw = Task eval
+       where
+               eval event evalOpts tree=:(TCInit taskId ts) iworld=:{IWorld|world}
+               = case TTYopen dev opts world of
+                       (False, _, world)
+                       # (err, world) = TTYerror world
+                       = (ExceptionResult (exception err), {iworld & world=world})
+                       (True, tty, world)
+                       # iworld = {iworld & world=world, resources=Just (TTYd tty)}
+                       = case addBackgroundTask 42 (BackgroundTask (serialDeviceBackgroundTask rw decodeFun encodeFun)) iworld of
+                               (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
+                               (Ok _, iworld) = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=True} NoRep (TCBasic taskId ts JSONNull False), iworld)
+
+               eval _ _ tree=:(TCBasic _ ts _ _) iworld
+               = (ValueResult NoValue {TaskEvalInfo|lastEvent=ts,removedTasks=[],refreshSensitive=False} NoRep tree, iworld)
+
+               eval event evalOpts tree=:(TCDestroy _) iworld=:{IWorld|resources,world}
+               # (TTYd tty) = fromJust resources
+               # (ok, world) = TTYclose tty world
+               # iworld = {iworld & world=world,resources=Nothing}
+               = case removeBackgroundTask  42 iworld of
+                       (Error e, iworld) = (ExceptionResult (exception "h"), iworld)
+                       (Ok _, iworld) = (DestroyedResult, iworld)
+
+serialDeviceBackgroundTask :: (Shared ([m],Bool,[n],Bool)) (String -> m) (n -> String) !*IWorld -> *IWorld
+serialDeviceBackgroundTask rw de en iworld
+       = case read rw iworld of
+               (Error e, iworld) = abort "share couldn't be read"
+               (Ok (r,rs,s,ss), iworld)
+               # (Just (TTYd tty)) = iworld.resources
+               # tty = writet (map en s) tty
+               # (ml, tty) = case TTYavailable tty of
+                       (False, tty) = ([], tty)
+                       (_, tty)
+                       # (l, tty) = TTYreadline tty
+                       = ([de l], tty)
+               # iworld = {iworld & resources=Just (TTYd tty)}
+               = case write (r++ml,rs,[],ss) rw iworld of
+                       (Error e, iworld) = abort "share couldn't be written"
+                       (Ok _, iworld) = case notify rw iworld of
+                               (Error e, iworld) = abort "share couldn't be notified"
+                               (Ok _, iworld) = iworld
+       where
+               writet :: [String] !*TTY -> *TTY
+               writet [] t = t
+               writet [x:xs] t = writet xs (TTYwrite x t)
+
+
 syncNetworkChannel :: String Int String (String -> m) (n -> String) (Shared ([m],Bool,[n],Bool)) -> Task () | iTask m & iTask n
 syncNetworkChannel server port msgSeparator decodeFun encodeFun channel
        = tcpconnect server port channel {ConnectionHandlers|onConnect=onConnect,whileConnected=whileConnected,onDisconnect=onDisconnect} @! ()
@@ -115,8 +205,10 @@ syncNetworkChannel server port msgSeparator decodeFun encodeFun channel
                onConnect _ (received,receiveStopped,send,sendStopped)
                        = (Ok "",if (not (isEmpty send)) (Just (received,False,[],sendStopped)) Nothing, map encodeFun send,False)
                whileConnected Nothing acc (received,receiveStopped,send,sendStopped)
+               | not (trace_tn "whilec nothing") = undef
                        = (Ok acc, Nothing, [], False)
                whileConnected (Just newData) acc (received,receiveStopped,send,sendStopped)
+               | not (trace_tn "whilec just") = undef
                # [acc:msgs] = reverse (split msgSeparator (concat [acc,newData]))
                # write = if (not (isEmpty msgs && isEmpty send))
                        (Just (received ++ map decodeFun (reverse msgs),receiveStopped,[],sendStopped))