diff --git a/Auto.hs b/Auto.hs index bc540d8..54da2f5 100644 --- a/Auto.hs +++ b/Auto.hs @@ -1,22 +1,21 @@ module Auto where -import Control.Monad.Trans.Reader (ReaderT, runReaderT, ask) +import Control.Monad.Reader (Reader, runReader, asks) import Control.Applicative ((<$>)) import qualified Data.Map as M +import Types -type Env a = (M.Map String a) - -envLookup :: (Show a) => String -> Auto a a +envLookup :: String -> Auto Parameter envLookup key = do - maybeVal <- M.lookup key <$> ask + maybeVal <- M.lookup key <$> asks envC case maybeVal of Just v -> return v Nothing -> error $ "Undefined environment variable: " ++ key -type Auto a = ReaderT (Env a) IO +type Auto = Reader Config -runAuto :: Auto a b -> Env a -> IO b -runAuto = runReaderT +runAuto :: Auto a -> Config -> a +runAuto = runReader \ No newline at end of file diff --git a/CCSDS.hs b/CCSDS.hs index 64e51ec..f5a5939 100644 --- a/CCSDS.hs +++ b/CCSDS.hs @@ -6,9 +6,11 @@ module CCSDS where import Data.BitVector import Control.Exception.Base (assert) import Control.Applicative ((<$>)) +import qualified Data.ByteString.Lazy as B import Common import Parameter import Auto +import Types packetVersionNumber :: BV @@ -27,7 +29,7 @@ sequenceCount :: BV sequenceCount = zeros 14 -packetDataLength :: (CCSDS a) => a -> Auto Parameter BV +packetDataLength :: (CCSDS a) => a -> Auto BV packetDataLength m = do pl <- length <$> payload m return . bitVec 16 $ length (secondaryHeader m) + pl @@ -41,11 +43,11 @@ class (Show a) => CCSDS a where secondaryHeader :: a -> [Byte] - payload :: a -> Auto Parameter [Byte] + payload :: a -> Auto [Byte] -primaryHeader :: (CCSDS a) => a -> Auto Parameter BV +primaryHeader :: (CCSDS a) => a -> Auto BV primaryHeader m = do dataLength <- packetDataLength m return $ packetVersionNumber @@ -57,20 +59,20 @@ primaryHeader m = do # dataLength -header :: (CCSDS a) => a -> Auto Parameter [Byte] +header :: (CCSDS a) => a -> Auto [Byte] header m = do pri <- bits2bytes . toBits <$> primaryHeader m return $ pri ++ secondaryHeader m -packet :: (CCSDS a) => a -> Auto Parameter [Byte] +packet :: (CCSDS a) => a -> Auto [Byte] packet m = do p <- payload m h <- swapBytes <$> header m return $ h ++ p -packCCSDS :: (CCSDS a) => a -> Auto Parameter [Byte] +packCCSDS :: (CCSDS a) => a -> Auto B.ByteString packCCSDS m = do p <- packet m pri <- primaryHeader m @@ -79,4 +81,4 @@ packCCSDS m = do let check1 = size pri == 6 * 8 --bits let check2 = length pld + length (secondaryHeader m) == len + 1 let checkAll = check1 -- && check2 - return $ assert checkAll p \ No newline at end of file + return $ assert checkAll (B.pack p) \ No newline at end of file diff --git a/Command.hs b/Command.hs index 99de227..50ebc19 100644 --- a/Command.hs +++ b/Command.hs @@ -7,22 +7,13 @@ module Command ( import Numeric (showHex) import GHC.Generics (Generic) import Data.Aeson (FromJSON) -import Parameter -import Common +import Types +import Parameter() -type CommandCode = Byte - - -data Command = Command { - cc :: CommandCode - ,parameters :: [Parameter] -} deriving (Generic) - instance FromJSON Command instance Show Command where - show (Command c ps) = "CMD: " ++ " cc:" ++ showHex c " " ++ show ps - + show (Command c ps) = "CMD: " ++ " cc:" ++ showHex c " " ++ show ps \ No newline at end of file diff --git a/Common.hs b/Common.hs index 5fd736d..f425778 100644 --- a/Common.hs +++ b/Common.hs @@ -1,12 +1,7 @@ module Common where import Data.BitVector hiding (showHex) -import Data.Word - - -type Byte = Word8 - -type Frequency = Double +import Types safeBitVec :: (Integral a, Show a) => Int -> a -> BV diff --git a/Controller.hs b/Controller.hs index 26ee744..bd3228d 100644 --- a/Controller.hs +++ b/Controller.hs @@ -4,29 +4,12 @@ module Controller where import Data.Aeson (FromJSON) import GHC.Generics (Generic) +import Types -data Controller = Controller { - meta :: ControllerMeta - ,sequenced :: [MessageMeta] - ,parallel :: [MessageMeta] -} deriving (Show, Generic) - -instance FromJSON Controller - - -data ControllerMeta = ControllerMeta { - ip :: String - ,port :: Integer -} deriving (Show, Generic) - instance FromJSON ControllerMeta - -data MessageMeta = MessageMeta { - file :: FilePath - ,frequency :: Double -} deriving (Show, Generic) +instance FromJSON Controller instance FromJSON MessageMeta diff --git a/Data.hs b/Data.hs new file mode 100644 index 0000000..a6f76b1 --- /dev/null +++ b/Data.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Data where + +import qualified Data.ByteString.Lazy as B +import Data.ByteString.Lazy.Builder +import Data.Vector (toList) +import Foreign.Marshal.Utils (fromBool) +import Control.Applicative ((<$>), (<*>)) +import Data.Aeson +import Data.Aeson.Types +import Types + + +packData :: Data -> [Byte] +packData (S s n) = (b2w (string7 s)) ++ replicate (n - length s) 0 +packData (B b) = b2w . word8 . fromBool $ b +packData (I8 i) = b2w . int8 $ i +packData (W8 w) = b2w . word8 $ w +packData (I16 i) = b2w . int16LE $ i +packData (W16 w) = b2w . word16LE $ w +packData (I32 i) = b2w . int32LE $ i +packData (W32 w) = b2w . word32LE $ w +packData (I64 i) = b2w . int64LE $ i +packData (W64 w) = b2w . word64LE $ w +packData (F f) = b2w . floatLE $ f +packData (D d) = b2w . doubleLE $ d +packData (Arr a) = concatMap packData a +packData _ = error "Invalid data type for packData." + + + +b2w :: Builder -> [Byte] +b2w = B.unpack . toLazyByteString + + +instance FromJSON Data where + + parseJSON (Object o) = do + typ <- o .: "type" + case typ of + "string" -> S <$> o .: "value" <*> o .: "length" + "bool" -> B <$> o .: "value" + "int8" -> I8 <$> o .: "value" + "uint8" -> W8 <$> o .: "value" + "int16" -> I16 <$> o .: "value" + "uint16" -> W16 <$> o .: "value" + "int32" -> I32 <$> o .: "value" + "uint32" -> W32 <$> o .: "value" + "int64" -> I64 <$> o .: "value" + "uint64" -> W64 <$> o .: "value" + "float" -> F <$> o .: "value" + "double" -> D <$> o .: "value" + "array" -> do + elemTyp <- (o .: "element_type") :: Parser String + vals <- (o .: "values") :: Parser Array + elems <- mapM (parseJSON . makeElem elemTyp) (toList vals) + return $ Arr elems + t -> error $ "Invalid argument type: " ++ t + where + makeElem t v = object ["type" .= t, "value" .= v] + + parseJSON _ = error "Invalid message definition." \ No newline at end of file diff --git a/Main.hs b/Main.hs index 6e33952..6205bdf 100644 --- a/Main.hs +++ b/Main.hs @@ -1,14 +1,28 @@ +{-# LANGUAGE NamedFieldPuns, FlexibleContexts #-} + + --import System.Environment (getArgs) import Control.Monad +import Control.Applicative ((<$>)) import Control.Concurrent +import System.FilePath.Posix (takeExtensions) +import System.IO (hFlush, stdout) +import Data.Aeson (FromJSON) +import qualified Data.ByteString.Lazy as B +import qualified Data.Map as M +import Data.List (transpose) +import Auto import Controller import Send import Parse +import Types +import CCSDS +import Message main :: IO () --main = mapM (parseFile >=> run) <$> getArgs -main = (parseFile >=> run) "main.ctrl" +main = (parseFile >=> runner) "main.ctrl" myForkIO :: IO () -> IO (MVar ()) @@ -22,10 +36,37 @@ myForkIOs :: [IO ()] -> IO () myForkIOs actions = mapM myForkIO actions >>= mapM_ takeMVar -run :: Controller -> IO () -run (Controller {meta=cm, sequenced=s, parallel=p}) = do - let actions = mapM_ go s : map go p +runner :: Controller -> IO () +runner (Controller {meta=cm, sequenced=s, parallel=p}) = --myForkIOs actions sequence_ actions where - go mm = void $ send cm (frequency mm) (file mm) \ No newline at end of file + actions = mapM_ (run cm) s : map (run cm) p + + +run :: ControllerMeta -> MessageMeta -> IO () +run (ControllerMeta {ip, port}) (MessageMeta {file, frequency}) = do + packed <- getPacked + forM_ packed $ (\p -> do + sendUDP ip port p + print p + hFlush stdout + threadDelay . round $ 1000000 / frequency + ) + where + getPacked = + case takeExtensions file of + ".tlm" -> pack <$> (parseFile file :: IO (MessageDef Telemetry)) + ".cmd" -> pack <$> (parseFile file :: IO (MessageDef Command)) + + +pack :: (FromJSON a, CCSDS (Message a)) => MessageDef a -> [B.ByteString] +pack (MessageDef {variables=vs, message=m}) = do + map (runAuto (packCCSDS m)) $ makeEnvs vs + where + varToPairs (Variable id_ ds) = [(id_, Parameter id_ d) | d <- ds] + makeEnvs vs = + let jaggedPairs = map varToPairs vs in + let smallestLen = minimum . map length $ jaggedPairs in + let flushPairs = map (take smallestLen) jaggedPairs in + map Config . map M.fromList . transpose $ flushPairs \ No newline at end of file diff --git a/Message.hs b/Message.hs index c75daf6..7f938d7 100644 --- a/Message.hs +++ b/Message.hs @@ -15,12 +15,9 @@ import Command import Telemetry import Parameter import Variable +import Types -type MessageID = Byte - - -data Message a = Message MessageID a deriving (Show) instance (FromJSON a) => FromJSON (Message a) where @@ -29,11 +26,6 @@ instance (FromJSON a) => FromJSON (Message a) where parseJSON _ = error "Invalid message definition." -data MessageDef a = MessageDef { - variables :: [Variable] - ,message :: Message a -} deriving (Show, Generic) - instance (FromJSON a) => FromJSON (MessageDef a) diff --git a/Parameter.hs b/Parameter.hs index 2501984..ea1a2e1 100644 --- a/Parameter.hs +++ b/Parameter.hs @@ -7,104 +7,28 @@ module Parameter ( import Control.Applicative ((<$>), (<*>)) import Data.Aeson -import Data.Aeson.Types -import Data.Int (Int8, Int16, Int32, Int64) -import Data.Word (Word8, Word16, Word32, Word64) -import Data.Vector (toList) import Numeric (showHex) -import qualified Data.ByteString.Lazy as B -import Data.ByteString.Lazy.Builder -import Foreign.Marshal.Utils (fromBool) import qualified Data.Text as T -import Common +import Types +import Data import Auto -data Parameter = S String String Int - | B String Bool - | I8 String Int8 - | W8 String Word8 - | I16 String Int16 - | W16 String Word16 - | I32 String Int32 - | W32 String Word32 - | I64 String Int64 - | W64 String Word64 - | F String Float - | D String Double - | Arr String [Parameter] - | Var String - - -packParam :: Parameter -> Auto Parameter [Byte] -packParam (S _ s n) = return $ b2w (string7 s) ++ replicate (n - length s) 0 -packParam (B _ b) = return $ b2w . word8 . fromBool $ b -packParam (I8 _ i) = return $ b2w . int8 $ i -packParam (W8 _ w) = return $ b2w . word8 $ w -packParam (I16 _ i) = return $ b2w . int16LE $ i -packParam (W16 _ w) = return $ b2w . word16LE $ w -packParam (I32 _ i) = return $ b2w . int32LE $ i -packParam (W32 _ w) = return $ b2w . word32LE $ w -packParam (I64 _ i) = return $ b2w . int64LE $ i -packParam (W64 _ w) = return $ b2w . word64LE $ w -packParam (F _ f) = return $ b2w . floatLE $ f -packParam (D _ d) = return $ b2w . doubleLE $ d -packParam (Arr _ ps) = concat <$> mapM packParam ps -packParam (Var name) = envLookup name >>= packParam - - -b2w :: Builder -> [Byte] -b2w = B.unpack . toLazyByteString +packParam :: Parameter -> Auto [Byte] +packParam (Parameter _ (Var name)) = envLookup name >>= packParam +packParam (Parameter _ d) = return . packData $ d instance FromJSON Parameter where - parseJSON (Object o) = do - typ <- o .: "type" - label <- o .:? "label" .!= "unnamed" - case typ of - "string" -> S label <$> o .: "value" <*> o .: "length" - "bool" -> B label <$> o .: "value" - "int8" -> I8 label <$> o .: "value" - "uint8" -> W8 label <$> o .: "value" - "int16" -> I16 label <$> o .: "value" - "uint16" -> W16 label <$> o .: "value" - "int32" -> I32 label <$> o .: "value" - "uint32" -> W32 label <$> o .: "value" - "int64" -> I64 label <$> o .: "value" - "uint64" -> W64 label <$> o .: "value" - "float" -> F label <$> o .: "value" - "double" -> D label <$> o .: "value" - "array" -> do - elemTyp <- (o .: "element_type") :: Parser String - vals <- (o .: "values") :: Parser Array - elems <- mapM (parseJSON . makeElem elemTyp) (toList vals) - return $ Arr label elems - t -> error $ "Invalid argument type: " ++ t - where - makeElem t v = object ["type" .= t, "value" .= v] - parseJSON (String s) = return $ Var (T.unpack s) + parseJSON (Object o) = Parameter <$> o .:? "label" .!= "unnamed"<*> parseJSON (Object o) + + parseJSON (String s) = return $ Parameter "var" (Var (T.unpack s)) parseJSON _ = error "Invalid parameter type." instance Show Parameter where - show p@(S l _ _) = showParam p l - show p@(B l _) = showParam p l - show p@(I8 l _) = showParam p l - show p@(W8 l _) = showParam p l - show p@(I16 l _) = showParam p l - show p@(W16 l _) = showParam p l - show p@(I32 l _) = showParam p l - show p@(W32 l _) = showParam p l - show p@(I64 l _) = showParam p l - show p@(W64 l _) = showParam p l - show p@(F l _) = showParam p l - show p@(D l _) = showParam p l - show p@(Arr l _) = showParam p l - show p@(Var l) = showParam p l - - -showParam :: Parameter -> String -> String -showParam p l = l ++ ":FIX" -- ++ concatMap (`showHex` "|") (packParam p) \ No newline at end of file + show (Parameter _ (Var id_)) = id_ ++ ":" ++ "" + show (Parameter s d) = s ++ ":" ++ concatMap (`showHex` "|") (packData d) diff --git a/Send.hs b/Send.hs index 8240d6c..0df8265 100644 --- a/Send.hs +++ b/Send.hs @@ -1,67 +1,12 @@ -{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-} - module Send ( - send + sendUDP ) where -import Control.Monad -import Control.Monad.IO.Class (liftIO) import Control.Applicative import Network.Socket hiding (sendTo, send) import Network.Socket.ByteString (sendTo) import qualified Data.ByteString.Lazy as B -import System.FilePath.Posix (takeExtensions) -import Control.Concurrent (threadDelay) -import Text.Show.Pretty (ppShow) -import System.IO -import qualified Data.Map as M -import Data.List (transpose) -import Data.Aeson (FromJSON) -import Controller -import Common -import Parse -import CCSDS -import Command -import Telemetry -import Parameter -import Message -import qualified Variable as V -import Auto - - -send :: ControllerMeta -> Frequency -> FilePath -> IO () -send meta freq file = - case takeExtensions file of - ".tlm" -> void (sendFile meta freq file :: IO (Message Telemetry)) - ".cmd" -> void (sendFile meta freq file :: IO (Message Command)) - - -sendFile :: (FromJSON a, CCSDS (Message a)) => ControllerMeta -> Frequency -> FilePath -> IO (Message a) -sendFile meta freq file = do - (MessageDef {variables=vs, message=m}) <- getFile - mapM_ (runAuto (sendCCSDS meta freq m)) $ makeEnvs vs - return m - where - --getFile :: (FromJSON a) => IO (MessageDef a) - getFile = parseFile file - varToPairs (V.F id_ vals) = [(id_, F id_ val) | val <- vals] - varToPairs (V.W8 id_ vals) = [(id_, W8 id_ val) | val <- vals] - --varToPairs _ = undefined - makeEnvs vs = - let jaggedPairs = map varToPairs vs in - let smallestLen = minimum . map length $ jaggedPairs in - let flushPairs = map (take smallestLen) jaggedPairs in - map M.fromList $ transpose flushPairs - - -sendCCSDS :: (CCSDS a) => ControllerMeta -> Frequency -> a -> Auto Parameter () -sendCCSDS (ControllerMeta {ip=ip, port=port}) freq ccsds = do - packed <- packCCSDS ccsds - liftIO $ sendUDP ip port . B.pack $ packed - mapM_ liftIO $ [putStrLn $ ppShow ccsds - ,hFlush stdout - ,threadDelay . round $ 1000000 / freq] sendUDP :: String -> Integer -> B.ByteString -> IO () diff --git a/Telemetry.hs b/Telemetry.hs index 772624d..553915a 100644 --- a/Telemetry.hs +++ b/Telemetry.hs @@ -6,10 +6,8 @@ module Telemetry ( import GHC.Generics (Generic) import Data.Aeson (FromJSON) -import Parameter - - -data Telemetry = Telemetry {parameters :: [Parameter]} deriving (Generic) +import Types +import Parameter() instance FromJSON Telemetry diff --git a/Types.hs b/Types.hs new file mode 100644 index 0000000..fa5567b --- /dev/null +++ b/Types.hs @@ -0,0 +1,86 @@ +{-# LANGUAGE DeriveGeneric #-} + + +module Types where + +import qualified Data.Map as M +import Data.Int (Int8, Int16, Int32, Int64) +import Data.Word (Word8, Word16, Word32, Word64) +import GHC.Generics + + +type Byte = Word8 + +type Frequency = Double + +type MessageID = Byte + +type CommandCode = Byte + +--data Endianness = BE | LE + + +data Data = S String Int + | B Bool + | I8 Int8 + | W8 Word8 + | I16 Int16 + | W16 Word16 + | I32 Int32 + | W32 Word32 + | I64 Int64 + | W64 Word64 + | F Float + | D Double + | Arr [Data] + | Var String deriving (Show) + + +data Parameter = Parameter String Data + + +data Variable = Variable String [Data] deriving (Show) + + +data Command = Command { + cc :: CommandCode + ,arguments :: [Parameter] +} deriving (Generic) + + +data Telemetry = Telemetry { + parameters :: [Parameter] +} deriving (Generic) + + +data Message a = Message MessageID a deriving (Show) + + +data MessageDef a = MessageDef { + variables :: [Variable] + ,message :: Message a +} deriving (Show, Generic) + + +data MessageMeta = MessageMeta { + file :: FilePath + ,frequency :: Double +} deriving (Show, Generic) + + +data Controller = Controller { + meta :: ControllerMeta + ,sequenced :: [MessageMeta] + ,parallel :: [MessageMeta] +} deriving (Show, Generic) + + +data ControllerMeta = ControllerMeta { + ip :: String + ,port :: Integer +} deriving (Show, Generic) + + +data Config = Config { + envC :: M.Map String Parameter +} diff --git a/Variable.hs b/Variable.hs index 37de0da..a4bfd10 100644 --- a/Variable.hs +++ b/Variable.hs @@ -5,15 +5,9 @@ module Variable ( Variable (..) ) where ---import Data.Int (Int8, Int16, Int32, Int64) -import Data.Word (Word8, Word16, Word32, Word64) import Data.Aeson import Data.Aeson.Types -import Control.Applicative ((<$>)) - - -data Variable = F String [Float] - | W8 String [Word8] deriving (Show) +import Types instance FromJSON Variable where @@ -25,8 +19,12 @@ instance FromJSON Variable where "range" -> makeRange element_type id_ _ -> undefined where - makeRange "float" id_ = F id_ <$> rangeList o - makeRange "uint8" id_ = W8 id_ <$> rangeList o + makeRange "float" id_ = do + vals <- rangeList o + return $ Variable id_ (map F vals) + makeRange "uint8" id_ = do + vals <- rangeList o + return $ Variable id_ (map W8 vals) makeRange _ id_ = undefined rangeList obj = do diff --git a/ac_noop.cmd b/ac_noop.cmd index f919e1b..ff605b0 100644 --- a/ac_noop.cmd +++ b/ac_noop.cmd @@ -1,5 +1,5 @@ { "mid": "0xCA", "cc" : 0, - "parameters": [] + "arguments": [] } diff --git a/auto.sublime-workspace b/auto.sublime-workspace index 4dfecf8..c20859c 100644 --- a/auto.sublime-workspace +++ b/auto.sublime-workspace @@ -3,6 +3,42 @@ { "selected_items": [ + [ + "ru", + "runIdentity" + ], + [ + "Messag", + "MessageDef" + ], + [ + "var", + "varToMap" + ], + [ + "mak", + "makeRangeList" + ], + [ + "Co", + "CommandCode" + ], + [ + "Mes", + "message" + ], + [ + "parse", + "parseJSON" + ], + [ + "Mess", + "MessageDef" + ], + [ + "data", + "dataLength" + ], [ "p", "parseJSON" @@ -95,10 +131,6 @@ "Comm", "Command" ], - [ - "Mes", - "MessageID" - ], [ "se", "secondaryHeader" @@ -482,43 +514,59 @@ [ "Steeri", "SteeringLawInfo" - ], - [ - "Steering", - "SteeringLawsInfo" - ], - [ - "SteeringLawInf", - "SteeringLawsInfo" - ], - [ - "Steerin", - "SteeringLawInfo" - ], - [ - "St", - "SteeringLawsInfo" - ], - [ - "defa", - "defaultSteeringLaw" - ], - [ - "Ac", - "AC_AppData" - ], - [ - "AC_Steer", - "AC_SteeringLawInfo_t" - ], - [ - "os", - "OS_printf" ] ] }, "buffers": [ + { + "file": "Main.hs", + "settings": + { + "buffer_size": 696, + "line_ending": "Unix" + } + }, + { + "file": "Command.hs", + "settings": + { + "buffer_size": 466, + "line_ending": "Unix" + } + }, + { + "file": "Auto.hs", + "settings": + { + "buffer_size": 677, + "line_ending": "Unix" + } + }, + { + "file": "Send.hs", + "settings": + { + "buffer_size": 2279, + "line_ending": "Unix" + } + }, + { + "file": "Types.hs", + "settings": + { + "buffer_size": 812, + "line_ending": "Unix" + } + }, + { + "file": "Parameter.hs", + "settings": + { + "buffer_size": 3345, + "line_ending": "Unix" + } + } ], "build_system": "", "command_palette": @@ -732,6 +780,29 @@ }, "file_history": [ + "/home/dan/Copy/projects/Auto/Common.hs", + "/home/dan/Copy/projects/Auto/Controller.hs", + "/home/dan/Copy/projects/Auto/CCSDS.hs", + "/home/dan/Copy/projects/Auto/Parse.hs", + "/home/dan/Copy/projects/Auto/Message.hs", + "/home/dan/Copy/projects/Auto/Telemetry.hs", + "/home/dan/Copy/projects/Auto/Variable.hs", + "/home/dan/Copy/projects/Auto/auto", + "/home/dan/Copy/projects/Auto/ac_set_mode.tlm", + "/home/dan/Copy/projects/Auto/main.ctrl", + "/home/dan/Copy/projects/Auto/Command.hs", + "/home/dan/Copy/projects/Auto/Parameter.hs", + "/home/dan/Copy/projects/Auto/auto.sublime-project", + "/home/dan/Copy/projects/Auto/Auto.hs", + "/home/dan/Copy/projects/Auto/README.md", + "/home/dan/Copy/projects/Auto/Send.hs", + "/home/dan/Copy/projects/Auto/Main.hs", + "/home/dan/Copy/projects/Auto/ac_noop.cmd", + "/home/dan/Copy/projects/Auto/.gitignore", + "/home/dan/Copy/projects/Auto/ekf.tlm", + "/home/dan/Copy/backup/.config/sublime-text-3/Packages/Alignment/Default (Linux).sublime-keymap", + "/home/dan/Copy/projects/Auto/cmg.tlm", + "/home/dan/Copy/projects/Auto/ops_test.cmd", "/home/dan/ACS/ACS/apps/ac/fsw/src/ac_autocode.c", "/home/dan/ACS/ACS/apps/pil_out/fsw/src/pil_out_app.c", "/home/dan/ACS/ACS/cfe/fsw/cfe-core/src/tbl/cfe_tbl_api.c", @@ -836,40 +907,18 @@ "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/birefringence.tex", "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/title.tex", "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/background.tex", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/tex/report.bib", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/slide8.tex", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/sucrose.png", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/images/Sucrose_and_fructose.png", - "/home/dan/Copy/backup/.config/sublime-text-3/Packages/User/Preferences.sublime-settings", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/presentation/pres.aux", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/tex/reportNotes.bib", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/tex/report.aux", - "/home/dan/Copy/Cornell/Semester8/4410/Lab1/tex/apssamp.aux", - "/home/dan/ACS/ACS/apps/lc/fsw/unit_test/output_CDS/lc_app.c.gcov", - "/home/dan/ACS/ACS/build/c901-vxworks/inc/osconfig.h", - "/home/dan/sem8/4410/Lab1/presentation/ref.tex", - "/home/dan/sem8/4410/Lab1/presentation/electro.tex", - "/home/dan/sem8/4410/Lab1/presentation/electro_apparatus.tex", - "/home/dan/sem8/4410/Lab1/tex/report.tex", - "/home/dan/sem8/4410/Lab1/presentation/macros.tex", - "/home/dan/sem8/4410/Lab1/presentation/faraday.tex", - "/home/dan/sem8/4410/Lab1/presentation/electro_results.tex", - "/home/dan/sem8/4410/Lab1/presentation/birefringence.tex", - "/home/dan/sem8/4410/Lab1/presentation/chiral.tex", - "/home/dan/sem8/4410/Lab1/presentation/title.tex", - "/home/dan/sem8/4410/Lab1/plot.hs", - "/home/dan/sem8/4410/Lab1/presentation/pres.tex", - "/home/dan/Copy/backup/.config/sublime-text-3/Packages/User/Distraction Free.sublime-settings" + "/home/dan/Copy/Cornell/Semester8/4410/Lab1/tex/report.bib" ], "find": { - "height": 34.0 + "height": 42.0 }, "find_in_files": { "height": 114.0, "where_history": [ + "", "*.h", "*.c", "*.h", @@ -981,134 +1030,134 @@ "case_sensitive": true, "find_history": [ - "CFE_TBL_BUF_MEMORY_BYTES", - "CFE_ES_PoolCreate", - "CFE_ES_PoolCreateEx", - "Size", - "PoolPtr->End", - "PoolPtr.End", - "PoolPtr", - "Pool_t", - "PoolPtr", - "Request won't fit in remaining memory", - "CFE_PSP_USER_RESERVED_SIZERequest won't fit in remaining memory", - "CFE_PSP_USER_RESERVED_SIZE", - "CFE_ES_USER_RESERVED_SIZE", - "CFE_PSP_USER_RESERVED_SIZE", - "CFE_ES_USER_RESERVED_SIZE", - "USER_RESERVED_MEM", - "MEM", - "USER_RESERVED_MEM", - "33554432", - "Cannot shmget User Reserved Area Shared memory Segment", - "BLOCK_SIZE", - "CFE_ES_ERR_MEM_BLOCK_SIZE", - "Request won't fit in remaining memory", - "CFE_TBL_MAX_SIMULTANEOUS_LOADS", - "C4000008", - "CFE_TBL_MAX_SIMULTANEOUS_LOADS", - "CFE_TBL_BUF_MEMORY_BYTES", - "52428815000000", - "524288", - "CFE_TBL_BUF_MEMORY_BYTES", - "524288", - "CFE_TBL_BUF_MEMORY_BYTES", - "80000", - "CFE_ES_MAX_BLOCK_SIZE", - "16384", - "TABLE", - "16384", - "Status", - "Failed to Register", - "CC000003", - "CC000001", - "AC_Att_Cmd_Gen_t", - "AC_ModelInputDataStores_t", - "att_cmds", - "ModelDataIncoming", - "ModelDataOutgoing", - "ModelDataIncoming", - "AC_Att_Cmd_Gen_t", - "= 0", - "NPS_PYR_Info", - "AC_AddSlew", - "AFRL_LPF_Info", - "ac_nps_pyr", - "NPS_PYR", - "NPS_PYR_SLEW_ENTRIES", - ";\n", - "AC_LPF_SLEW_ENTRIES", - "NPS_PYR_Info", - "AFRL_LPF_Info", - "NPS_PYR_Info", - "AC_LPF_SLEW_ENTRIES", - "AC_InitSlews", - "();", - "AC_LoadSlewTable", - "SwitchSlew", - "10000", - "ekf", - "a+b", - "x2", - "x3", - "step1", - "main", - "step1s", - "step1_0", - "step1", - "packParam", - "Arr", - "time", - "Message", - "Variable", + "Endianness", + "endianness", + "Env", + "type", + "getFile", + "Auto Parameter", + "Auto", + "Common", + "import", + "IO", + "hflush", + "Class", + "String", + "runWriterT", + "String", + "Writer", + "Auto", + "Text", + "showParam", + "ppShow", + "o", + "rangeList", + "makeRangeList", + "o", + "cc", + "ppShow", + "Telemetry", "Command", - "MessageMeta", - "Message", + "myForkIOs", + "MessageDef", + "ScopedTypeVariables", "Command", - "import", - "cmd", + "DeriveGeneric", + "Show", + "show", + "undefined", "Command", + "payload", + " = ", + " =", + "Telemetry", + "(Command", + " =", + "Telemetry", + "Command", + "fromJSON", + "Common", + "Generic", + "myForkIOs", + "hi", + "cleanParis", + "varToMap", + "pairs", + "tlm", + "file", + "meta", + "Parameter", + "Telemetry", + "ccsds", + "tlm", + "Telemetry", + "tlm", + "envs", + "tlm", + "Telemetry", + "liftIO", + "tlm", + "Parameter", + ", ", + "Command", + "cmgs", + "float", + "t_gps1980", + "time", + "print", + "envs", + "print", + "liftIO", + "IO", + "MonadIO", + "environment", + "undefined", + "Parameter", + "cc", + "mid", + "cc", "Message", - "Controller", - "Send", + "myForkIOs", + "run", + "Parameter", + "Variable", + "mappings", + "name", + "runRepeat", + "send", + ">>=", "Generic", "eitherDecode", - "instance FromJSON", - "DeriveGeneric", - "offset", + "Command", + "messages", + "MessageFile", + "case", + "start", + "<-", "end", - "10", "start", - "float", - "element_type", - "range", - "message", - "variable", - "repetition", - "qualified", - "replace", - "Lazy", - "showHex", - "hiding", - "strs", - "String", - "10000", - "parseFile", - "ctrl", - ", ", - "ctrl", - "Right", - "v_x", - "v_y", - "array", + "Telemetry", + "varDef", + " <-", + "mVars", + "mVarDef", + "Var", + "label", + "string", + "typ", "type", - "uint8a", - "t_gps1980", - "float", - "enabled_CMGs", - "uint8", - " \"", - "80" + "Parameter", + "data", + "Parameter", + "eter\n ,end :: Paramet", + "Parameter", + "varDef", + "vars", + "Var", + "Variable", + "a", + "VariableDef", + "MessageDef" ], "highlight": true, "in_selection": false, @@ -1157,14 +1206,462 @@ "groups": [ { + "selected": 4, "sheets": [ + { + "buffer": 0, + "file": "Main.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 696, + "regions": + { + }, + "selection": + [ + [ + 510, + 510 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "syntax": "Packages/SublimeHaskell/Syntaxes/Haskell-SublimeHaskell.tmLanguage" + }, + "translation.x": -0.0, + "translation.y": 360.0, + "zoom_level": 1.0 + }, + "stack_index": 2, + "type": "text" + }, + { + "buffer": 1, + "file": "Command.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 466, + "regions": + { + }, + "selection": + [ + [ + 209, + 209 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "syntax": "Packages/SublimeHaskell/Syntaxes/Haskell-SublimeHaskell.tmLanguage" + }, + "translation.x": 0.0, + "translation.y": 0.0, + "zoom_level": 1.0 + }, + "stack_index": 4, + "type": "text" + }, + { + "buffer": 2, + "file": "Auto.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 677, + "regions": + { + }, + "selection": + [ + [ + 500, + 500 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "syntax": "Packages/SublimeHaskell/Syntaxes/Haskell-SublimeHaskell.tmLanguage" + }, + "translation.x": 0.0, + "translation.y": 216.0, + "zoom_level": 1.0 + }, + "stack_index": 3, + "type": "text" + }, + { + "buffer": 3, + "file": "Send.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 2279, + "regions": + { + }, + "selection": + [ + [ + 701, + 701 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "rulers": + [ + 120 + ], + "syntax": "Packages/SublimeHaskell/Syntaxes/Haskell-SublimeHaskell.tmLanguage", + "tab_size": 4, + "translate_tabs_to_spaces": true, + "wrap_width": 120 + }, + "translation.x": 0.0, + "translation.y": 656.0, + "zoom_level": 1.0 + }, + "stack_index": 1, + "type": "text" + }, + { + "buffer": 4, + "file": "Types.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 812, + "regions": + { + }, + "selection": + [ + [ + 744, + 744 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "syntax": "Packages/Haskell/Haskell.tmLanguage" + }, + "translation.x": 0.0, + "translation.y": 482.0, + "zoom_level": 1.0 + }, + "stack_index": 0, + "type": "text" + }, + { + "buffer": 5, + "file": "Parameter.hs", + "semi_transient": false, + "settings": + { + "buffer_size": 3345, + "regions": + { + }, + "selection": + [ + [ + 3330, + 3330 + ] + ], + "settings": + { + "BracketHighlighterBusy": false, + "WordCountShouldRun": true, + "bh_regions": + [ + "bh_round", + "bh_round_center", + "bh_round_open", + "bh_round_close", + "bh_single_quote", + "bh_single_quote_center", + "bh_single_quote_open", + "bh_single_quote_close", + "bh_unmatched", + "bh_unmatched_center", + "bh_unmatched_open", + "bh_unmatched_close", + "bh_square", + "bh_square_center", + "bh_square_open", + "bh_square_close", + "bh_regex", + "bh_regex_center", + "bh_regex_open", + "bh_regex_close", + "bh_angle", + "bh_angle_center", + "bh_angle_open", + "bh_angle_close", + "bh_curly", + "bh_curly_center", + "bh_curly_open", + "bh_curly_close", + "bh_default", + "bh_default_center", + "bh_default_open", + "bh_default_close", + "bh_tag", + "bh_tag_center", + "bh_tag_open", + "bh_tag_close", + "bh_double_quote", + "bh_double_quote_center", + "bh_double_quote_open", + "bh_double_quote_close" + ], + "syntax": "Packages/SublimeHaskell/Syntaxes/Haskell-SublimeHaskell.tmLanguage", + "tab_size": 2, + "translate_tabs_to_spaces": true + }, + "translation.x": 0.0, + "translation.y": 2027.0, + "zoom_level": 1.0 + }, + "stack_index": 5, + "type": "text" + } ] } ], "incremental_find": { - "height": 34.0 + "height": 32.0 }, "input": { @@ -1224,7 +1721,7 @@ "project": "auto.sublime-project", "replace": { - "height": 64.0 + "height": 60.0 }, "save_all_on_build": true, "select_file": @@ -1233,125 +1730,273 @@ "selected_items": [ [ - "cfe_psp_memory", - "psp/fsw/pc-linux/src/cfe_psp_memory.c" + "common", + "Common.hs" ], [ - "cfe_psp", - "psp/fsw/shared/cfe_psp_eeprom.c" + "send", + "Send.hs" ], [ - "cfepspconfi", - "psp/fsw/pc-linux/inc/cfe_psp_config.h" + "ccsds", + "CCSDS.hs" ], [ - "cfe_pla", - "build/x86-linux/inc/cfe_platform_cfg.h" + "para", + "Parameter.hs" + ], + [ + "com", + "Command.hs" + ], + [ + "auot", + "Auto.hs" ], [ "auto", - "apps/ac/fsw/src/ac_autocode.c" + "Auto.hs" ], [ - "ac_ap.", - "apps/ac/fsw/src/ac_app.c" + "tele", + "Telemetry.hs" ], [ - "ac_autocode", - "build/c901-vxworks/ac/ac_autocode.lis" + "command", + "Command.hs" ], [ - "pil_out.c", - "apps/pil_out/fsw/src/pil_out_app.c" + "parse", + "Parse.hs" ], [ - "ac_app.c", - "apps/ac/fsw/src/ac_app.c" + "var", + "Variable.hs" ], [ - "cmg", - "cmg.msg" + "mess", + "Message.hs" ], [ - "tele", + "ccss", + "CCSDS.hs" + ], + [ + "main", + "Main.hs" + ], + [ + "comm", + "Command.hs" + ], + [ + "comma", + "Command.hs" + ], + [ + "tel", "Telemetry.hs" ], [ - "fog", - "fog.msg" + "pars", + "Parse.hs" ], [ - "main.ctr", - "main.ctrl" + "cont", + "Controller.hs" ], [ - "fo", - "~/sem8/QuantumInfo/hw5/fog.msg" + "", + "ac_set_mode.tlm" + ], + [ + "ac", + "ac_set_mode.tlm" ], [ "main.ctrl", "main.ctrl" ], [ - "ccsds", - "CCSDS.hs" + "mian", + "Main.hs" ], [ - "para", - "Parameter.hs" + "aut", + "Auto.hs" ], [ - "mess", - "Message.hs" + "au", + "Auto.hs" ], [ - "command", - "Command.hs" + "ac_", + "ac_set_mode.tlm" ], [ - "send", - "Send.hs" + "prse", + "Parse.hs" ], [ - "main", + "min", "Main.hs" ], [ - "contr", - "Controller.hs" + "comman", + "Command.hs" ], [ - "pr", - "Parse.hs" + ".cmd", + "ac_noop.cmd" ], [ - "conm", - "Common.hs" + "main.c", + "main.ctrl" ], [ - "ac", + "ac_set", "ac_set_mode.tlm" ], [ - "contro", - "Controller.hs" + "vara", + "Variable.hs" ], [ - "comman", - "Command.hs" + "vari", + "Variable.hs" ], [ "message", "Message.hs" ], [ - "c", - "Controller.hs" + "sn", + "Send.hs" + ], + [ + "ss", + "Send.hs" + ], + [ + "telem", + "Telemetry.hs" + ], + [ + "mes", + "Message.hs" + ], + [ + "commn", + "Common.hs" + ], + [ + "messag", + "Message.hs" + ], + [ + "pasre", + "Parse.hs" + ], + [ + "messg", + "Message.hs" + ], + [ + "param", + "Parameter.hs" + ], + [ + "par", + "Parameter.hs" + ], + [ + "tlm", + "ac_set_mode.tlm" ], [ "ctrl", "main.ctrl" ], + [ + "acset", + "ac_set_mode.tlm" + ], + [ + "ops", + "ops_test.cmd" + ], + [ + "ekf", + "ekf.tlm" + ], + [ + "cfe_psp_memory", + "psp/fsw/pc-linux/src/cfe_psp_memory.c" + ], + [ + "cfe_psp", + "psp/fsw/shared/cfe_psp_eeprom.c" + ], + [ + "cfepspconfi", + "psp/fsw/pc-linux/inc/cfe_psp_config.h" + ], + [ + "cfe_pla", + "build/x86-linux/inc/cfe_platform_cfg.h" + ], + [ + "ac_ap.", + "apps/ac/fsw/src/ac_app.c" + ], + [ + "ac_autocode", + "build/c901-vxworks/ac/ac_autocode.lis" + ], + [ + "pil_out.c", + "apps/pil_out/fsw/src/pil_out_app.c" + ], + [ + "ac_app.c", + "apps/ac/fsw/src/ac_app.c" + ], + [ + "cmg", + "cmg.msg" + ], + [ + "fog", + "fog.msg" + ], + [ + "main.ctr", + "main.ctrl" + ], + [ + "fo", + "~/sem8/QuantumInfo/hw5/fog.msg" + ], + [ + "contr", + "Controller.hs" + ], + [ + "pr", + "Parse.hs" + ], + [ + "conm", + "Common.hs" + ], + [ + "contro", + "Controller.hs" + ], + [ + "c", + "Controller.hs" + ], [ "cabal", "Auto.cabal" @@ -1360,10 +2005,6 @@ "mode", "ac_set_mode.msg" ], - [ - "", - "3a.tex" - ], [ "1b", "1b.tex" @@ -1380,14 +2021,6 @@ "1a", "1a.tex" ], - [ - "ekf", - "ekf.msg" - ], - [ - "tel", - "Telemetry.hs" - ], [ "test", "ops_test.msg" @@ -1400,30 +2033,14 @@ "main.", "main.ctrl" ], - [ - "main.c", - "main.ctrl" - ], [ "control", "Controller.hs" ], - [ - "ops", - "ops_test.msg" - ], [ "cmmon", "Common.hs" ], - [ - "ccss", - "CCSDS.hs" - ], - [ - "telem", - "Telemetry.hs" - ], [ "op", "ops_test.msg" @@ -1432,10 +2049,6 @@ "opt", "ops_test.msg" ], - [ - "common", - "Common.hs" - ], [ "ref", "ref.tex" @@ -1627,122 +2240,6 @@ [ "pre", "pres.tex" - ], - [ - "chil", - "chiral.tex" - ], - [ - "suc", - "sucrose.png" - ], - [ - "1", - "slide1.tex" - ], - [ - "2", - "slide2.tex" - ], - [ - "slid1", - "slide1.tex" - ], - [ - "sli", - "slide8.tex" - ], - [ - "slide8", - "slide8.tex" - ], - [ - "slid", - "slide2.tex" - ], - [ - "slide2", - "slide2.tex" - ], - [ - "slide", - "slide2.tex" - ], - [ - "beam", - "beamerthemeKalgan.sty" - ], - [ - "theme", - "beamerthemeKalgan.sty" - ], - [ - "cmg_msg", - "apps/cmg/fsw/src/cmg_msg.h" - ], - [ - "cmg_app.h", - "apps/cmg/fsw/src/cmg_app.h" - ], - [ - "ekf_ap", - "apps/ekf/fsw/src/ekf_app.h" - ], - [ - "ac_auto", - "apps/ac/fsw/src/ac_autocode.c" - ], - [ - "ac_a", - "apps/ac/fsw/src/ac_app.h" - ], - [ - "param", - "Parameter.hs" - ], - [ - "comm", - "Command.hs" - ], - [ - "ccsd", - "CCSDS.hs" - ], - [ - "ccs", - "CCSDS.hs" - ], - [ - "ccdss", - "CCSDS.hs" - ], - [ - "coma", - "Command.hs" - ], - [ - "cc", - "CCSDS.hs" - ], - [ - "json", - "test.json" - ], - [ - "main.hs", - "Main.hs" - ], - [ - "ma", - "Message.hi" - ], - [ - "builds", - "build/x86-linux/build_with_sls.sh" - ], - [ - "ekf_app.h", - "apps/ekf/fsw/src/ekf_app.h" ] ], "width": 0.0