Skip to content

Commit

Permalink
Add config parser and sample
Browse files Browse the repository at this point in the history
  • Loading branch information
bugarela committed Jun 29, 2022
1 parent 50346da commit 9b8019f
Show file tree
Hide file tree
Showing 3 changed files with 72 additions and 7 deletions.
34 changes: 34 additions & 0 deletions ConfigParser.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

module ConfigParser where

import Data.Aeson
import GHC.Generics
import qualified Data.ByteString.Lazy as B

jsonFile :: FilePath
jsonFile = "config-sample.json"

data DistributionConfig = Config [ProcessConfig] [String] deriving (Show,Generic)

data ProcessConfig = PConfig String [String] deriving (Show,Generic)

instance FromJSON DistributionConfig where
parseJSON = withObject "DistribuitionConfig" $ \obj -> do
ps <- obj .: "processes"
vs <- obj .: "shared_variables"
return (Config ps vs)

instance FromJSON ProcessConfig where
parseJSON = withObject "ProcessConfig" $ \obj -> do
i <- obj .: "process_id"
as <- obj .: "actions"
return (PConfig i as)

parseConfig :: FilePath -> IO (Either String DistributionConfig)
parseConfig file = do content <- B.readFile file
return (eitherDecode content)

-- main :: IO ()
-- main = parseJson jsonFile >>= print
16 changes: 9 additions & 7 deletions Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,15 @@ import Elixir
import Head
import Parser (parseTla)
import JSONParser (parseJson)
import ConfigParser (parseConfig)

convert mode a init next = do ls <- if mode == "tla" then parseTla a else parseJson a
case ls of
Left e -> putStrLn e >> return[]
Right (m, ds) -> let f = "elixir/lib/generated_code/" ++ filename m
in writeFile f (generate (Spec m init next ds)) >> return f
convert mode init next config ls = do case ls of
Left e -> putStrLn e >> return[]
Right (m, ds) -> let f = "elixir/lib/generated_code/" ++ filename m
in writeFile f (generate (Spec m init next ds)) >> return f

main = do (mode:name:i:n:_) <- getArgs
f <- convert mode name i n
main = do (mode:name:i:n:configFile:_) <- getArgs
config <- parseConfig configFile
ls <- if mode == "tla" then parseTla name else parseJson name
f <- convert name i n config ls
putStrLn ("Elixir file written to " ++ f)
29 changes: 29 additions & 0 deletions config-sample.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
{
"processes": [
{
"process_id": "node0",
"actions": [
"InitiateProbe",
"SendMsg(0)",
"Deactivate(0)"
]
},
{
"process_id": "node1",
"actions": [
"PassToken(1)",
"SendMsg(1)",
"Deactivate(1)"
]
},
{
"process_id": "node2",
"actions": [
"PassToken(2)",
"SendMsg(2)",
"Deactivate(2)"
]
}
],
"shared_variables": ["tcolor", "tpos", "active"]
}

0 comments on commit 9b8019f

Please sign in to comment.