Skip to content

Commit

Permalink
Cleaned up printed output, added new command and telemetry definition…
Browse files Browse the repository at this point in the history
…s, added times to message meta.
  • Loading branch information
dangirsh committed Apr 26, 2014
1 parent 5d10ec0 commit 10d066d
Show file tree
Hide file tree
Showing 19 changed files with 244 additions and 120 deletions.
1 change: 0 additions & 1 deletion CCSDS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ import Control.Exception.Base (assert)
import Control.Applicative ((<$>))
import qualified Data.ByteString.Lazy as B
import Common
import Parameter
import Auto
import Types

Expand Down
9 changes: 3 additions & 6 deletions Command.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,9 @@
{-# LANGUAGE DeriveGeneric #-}

module Command (
Command (Command)
) where

import Control.Applicative ((<$>))
import Numeric (showHex)
import GHC.Generics (Generic)
import Common
import Data.Aeson (FromJSON)
import Auto
import Types
Expand All @@ -19,5 +16,5 @@ instance FromJSON Command
instance AutoShow Command where

autoShow (Command c ps) = do
sp <- concat <$> mapM autoShow ps
return $ "CMD::" ++ " cc:" ++ showHex c " " ++ sp
sp <- concatMap ("\n\t" ++) <$> mapM autoShow ps
return $ "cc:" ++ showHex' c ++ " " ++ sp
7 changes: 7 additions & 0 deletions Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Common where

import Data.BitVector hiding (showHex)
import Types
import Numeric (showHex)


safeBitVec :: (Integral a, Show a) => Int -> a -> BV
Expand All @@ -28,3 +29,9 @@ swapBytes :: [Byte] -> [Byte]
swapBytes [] = []
swapBytes (b1:b2:bs) = b2:b1:swapBytes bs
swapBytes _ = error "Must be an even number of bytes to swap."


showHex' :: (Integral a, Show a) => a -> String
showHex' x = if length s == 1 then '0':s else s
where
s = showHex x ""
8 changes: 4 additions & 4 deletions Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,17 +6,17 @@ 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 Control.Applicative ((<$>))
import Data.Aeson
import Data.Aeson.Types
import Data.List.Split
import Types
import Debug.Trace (trace)
--import Debug.Trace (trace)
import qualified Data.Text as T


packData :: Data -> [Byte]
packData (S (s, n)) = (b2w (string7 s)) ++ replicate (n - length s) 0
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
Expand Down Expand Up @@ -49,7 +49,7 @@ instance FromJSON Data where
"string" -> do
(Number len) <- o .: "length" :: Parser Value
val <- o .: "value" :: Parser Value
return $ fromParse (typ ++ ":" ++ (show len)) val
return $ fromParse (typ ++ ":" ++ show len) val
_ -> fromParse typ <$> o .: "value"
where
makeElem t v = object ["type" .= t, "value" .= v]
Expand Down
18 changes: 8 additions & 10 deletions Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,19 +29,17 @@ main = getArgs >>= mapM_ (parseFile >=> runner)
runner :: Controller -> IO ()
runner (Controller {meta, sequenced, parallel}) = do
s <- async $ mapM_ (run meta) sequenced
mapConcurrently (run meta) parallel
_ <- mapConcurrently (run meta) parallel
wait s

--sequence_ $ mapM_ (run meta) sequenced : map (run meta) parallel
--myForkIOs $ mapM_ (run meta) sequenced : map (run meta) parallel


run :: ControllerMeta -> MessageMeta -> IO ()
run (ControllerMeta {ip, port}) (MessageMeta {file, frequency}) = do
packed <- uncurry zip <$> getPacked
forM_ packed (\(bs, s) -> do
run (ControllerMeta {ip, port}) (MessageMeta {file, frequency, times}) = do
packed <- getPacked
putStrLn $ "Starting to send " ++ file ++ " at " ++ (show frequency) ++ "Hz " ++ (show times) ++ " times.\n"
forM_ (take times packed) (\(bs, s) -> do
sendUDP ip port bs
print s
putStrLn $ file ++ ": " ++ s ++ "\n"
hFlush stdout
threadDelay . round $ 1000000 / frequency
)
Expand All @@ -53,8 +51,8 @@ run (ControllerMeta {ip, port}) (MessageMeta {file, frequency}) = do
ext -> error $ "Unknown file extension: " ++ ext


pack :: (FromJSON a, CCSDS (Message a), AutoShow a) => MessageDef a -> ([B.ByteString], [String])
pack (MessageDef {variables=vs, message=m}) = (f packCCSDS, f autoShow)
pack :: (FromJSON a, CCSDS (Message a), AutoShow a) => MessageDef a -> [(B.ByteString, String)]
pack (MessageDef {variables=vs, message=m}) = zip (f packCCSDS) (f autoShow)
where
f g = map (runAuto (g m)) envs
varToPairs (Variable id_ ds) = [(id_, Parameter id_ d) | d <- ds]
Expand Down
11 changes: 5 additions & 6 deletions Message.hs
Original file line number Diff line number Diff line change
@@ -1,21 +1,20 @@
{-# LANGUAGE OverloadedStrings, DeriveGeneric, FlexibleInstances, RankNTypes #-}
{-# LANGUAGE OverloadedStrings, FlexibleInstances, RankNTypes #-}

module Message (
Message (..)
,MessageDef (..)
) where

import Data.Aeson (FromJSON, parseJSON, (.:), Value(Object))
import GHC.Generics (Generic)
import Control.Applicative ((<$>), (<*>))
import Numeric (showHex)
import Common
import Data.BitVector (fromBool)
import Common
import CCSDS
import Command
import Telemetry
import Parameter
import Variable
import Variable()
import Types
import Auto

Expand Down Expand Up @@ -47,7 +46,7 @@ instance CCSDS (Message Command) where

applicationProcessId (Message mid _) = safeBitVec 11 mid

secondaryHeader (Message _ (Command cc _)) = [cc, 0]
secondaryHeader (Message _ (Command c _)) = [c, 0]

payload (Message _ (Command _ ps)) = concat <$> mapM packParam ps

Expand All @@ -56,4 +55,4 @@ instance (AutoShow a) => AutoShow (Message a) where

autoShow (Message mid m) = do
sm <- autoShow m
return $ "MID: " ++ (showHex mid "") ++ " " ++ sm
return $ "mid: " ++ showHex' mid ++ " " ++ sm
4 changes: 2 additions & 2 deletions Parameter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Parameter (

import Control.Applicative ((<$>), (<*>))
import Data.Aeson
import Numeric (showHex)
import Common
import qualified Data.Text as T
import Types
import Data
Expand All @@ -32,4 +32,4 @@ instance AutoShow Parameter where

autoShow p@(Parameter s _) = do
packed <- packParam p
return $ s ++ ":" ++ concatMap (`showHex` "|") packed
return $ s ++ ": " ++ concatMap ((++ "|") . showHex') packed
7 changes: 2 additions & 5 deletions Telemetry.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,8 @@
{-# LANGUAGE DeriveGeneric #-}

module Telemetry (
Telemetry(Telemetry)
) where

import Control.Applicative ((<$>))
import GHC.Generics (Generic)
import Data.Aeson (FromJSON)
import Types
import Auto
Expand All @@ -17,5 +14,5 @@ instance FromJSON Telemetry
instance AutoShow Telemetry where

autoShow (Telemetry ps) = do
sp <- concat <$> mapM autoShow ps
return $ "TLM: " ++ sp
sp <- concatMap ("\n\t" ++) <$> mapM autoShow ps
return sp
1 change: 1 addition & 0 deletions Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ data MessageDef a = MessageDef {
data MessageMeta = MessageMeta {
file :: FilePath
,frequency :: Double
,times :: Int
} deriving (Generic)


Expand Down
11 changes: 7 additions & 4 deletions ac_noop.cmd
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
{
"mid": "0xCA",
"cc" : 0,
"arguments": []
}
"variables": [],
"message": {
"mid": "0xCA",
"cc" : 0,
"arguments": []
}
}
Binary file modified auto
Binary file not shown.
14 changes: 14 additions & 0 deletions cdh.tlm
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{
"variables": [],
"message": {
"mid": "0xBD",
"parameters": [
{
"type": "array",
"element_type": "float",
"values": [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14],
"label": "w"
}
]
}
}
73 changes: 41 additions & 32 deletions cmg.tlm
Original file line number Diff line number Diff line change
@@ -1,34 +1,43 @@
{
"mid": "0xC3",
"parameters": [
{
"type": "uint8",
"value": 0,
"label": "enabled_CMGs"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "GimbalRate"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "GimbalAngle"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "RotorSpeed"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "RotorTorque"
}
]
"variables": [],
"message": {
"mid": "0xC3",
"parameters": [
{
"type": "uint8",
"value": 0,
"label": "enabled_CMGs"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "GimbalRate"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "GimbalAngle"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "RotorSpeed"
},
{
"type": "array",
"element_type": "float",
"values": [0,0,0,0,0,0,0,0],
"label": "RotorTorque"
},
{
"type": "array",
"element_type": "uint8",
"values": [0,0,0],
"label": "padding"
}
]
}
}
Loading

0 comments on commit 10d066d

Please sign in to comment.