Skip to content
This repository has been archived by the owner on May 24, 2021. It is now read-only.

Commit

Permalink
Parse MBL
Browse files Browse the repository at this point in the history
  • Loading branch information
jazcarate committed Aug 15, 2020
1 parent 931af0a commit c179930
Show file tree
Hide file tree
Showing 10 changed files with 106 additions and 10 deletions.
2 changes: 1 addition & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ repl: ## Repl
nix-shell \
--run "cabal new-repl"

run: ## Run de program in dev mode. Pass arguments in ARGS var
run: ## Run de program in dev mode. Pass arguments in ARGS
nix-shell \
--run "cabal new-run marble -- $$ARGS"

Expand Down
2 changes: 2 additions & 0 deletions marble-os.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ library
exposed-modules: App
, Duration
, Args
, Mbl
build-depends: text
, time
, optparse-applicative
Expand All @@ -44,6 +45,7 @@ test-suite marble-os-test
main-is: Spec.hs
other-modules: AppSpec
, DurationSpec
, MblSpec
build-depends: marble-os
, hspec

14 changes: 10 additions & 4 deletions src/App.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,17 @@
module App where

import Args ( args )

import Args ( args
, path
)
import Mbl ( parseMbl, interpret )
import qualified Data.ByteString as BS
import qualified Data.Text as T

main :: IO ()
main = do
config <- args
print config
config <- args
contents <- BS.readFile $ T.unpack $ path config
mbl <- either (fail) pure $ parseMbl contents
interpret mbl
putStrLn "3"
putStrLn "4"
6 changes: 3 additions & 3 deletions src/Args.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,10 @@ import qualified Duration as D
import qualified Data.String as S

data Configuration = Configuration
{ config :: T.Text
{ path :: T.Text
, repeat :: Bool
, tick :: D.Duration
, delimiter :: T.Text } deriving (Show)
, tick :: D.Duration
, delimiter :: T.Text }

configuration :: Parser Configuration
configuration =
Expand Down
4 changes: 2 additions & 2 deletions src/Duration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ data DurMinute = DurMinute Int (Maybe DurSecond) deriving (Eq, Ord, Show)
data Duration = DurationMicrosecond DurMicrosecond
| DurationMillisecond DurMillisecond
| DurationSecond DurSecond
| DurationMinute DurMinute deriving (Eq, Ord, Show)
| DurationMinute DurMinute deriving (Eq, Show)

duration :: Parser Duration
duration =
Expand Down Expand Up @@ -75,4 +75,4 @@ toMicroseconds dur = case dur of
dmToUs (DurMinute m mbs) = m * 60_000_000 + maybe 0 dsToUs mbs

seconds :: Int -> Duration
seconds = DurationSecond . flip DurSecond Nothing
seconds = DurationSecond . flip DurSecond Nothing
12 changes: 12 additions & 0 deletions src/Mbl.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Mbl where

import qualified Mbl.Types as Types
import qualified Mbl.Parser as Parser
import qualified Mbl.Interpreter as Interpreter
import qualified Data.ByteString as BS

parseMbl :: BS.ByteString -> Either String Types.MBL
parseMbl = Parser.parse

interpret :: Types.MBL -> IO ()
interpret = Interpreter.interpret
8 changes: 8 additions & 0 deletions src/Mbl/Interpreter.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Mbl.Interpreter where

import Mbl.Types
import qualified Control.Concurrent as C


interpret :: MBL -> IO ()
interpret _ = C.threadDelay 30000000
32 changes: 32 additions & 0 deletions src/Mbl/Parser.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
module Mbl.Parser where

import Prelude hiding ( takeWhile
, print
)
import Data.Attoparsec.ByteString.Char8
( Parser
, endOfInput
, parseOnly
, char
, takeWhile1
)
import Data.ByteString ( ByteString )
import Control.Applicative ( many
, (<|>)
)
import Mbl.Types

parse :: ByteString -> Either String MBL
parse = parseOnly (mbl <* endOfInput)

delimiter :: Char
delimiter = '-'

wait :: Parser Action
wait = char delimiter *> pure Wait

print :: Parser Action
print = Print <$> takeWhile1 (\c -> c /= delimiter)

mbl :: Parser MBL
mbl = many $ wait <|> print
8 changes: 8 additions & 0 deletions src/Mbl/Types.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Mbl.Types where


import Data.ByteString ( ByteString )

data Action = Wait | Print ByteString deriving (Show, Eq)

type MBL = [Action]
28 changes: 28 additions & 0 deletions test/MblSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
module MblSpec where

import Test.Hspec
import Mbl
import Mbl.Types

-- TODO spaces between

spec :: Spec
spec = do
describe "Mbl" $ do
describe "Simple" $ do
it "can parse waits" $ do
parseMbl "---" `shouldBe` Right [Wait, Wait, Wait]
it "can parse prints" $ do
parseMbl "foo" `shouldBe` Right [Print "foo"]
describe "Combo" $ do
it "can parse waits and prints" $ do
parseMbl "-foo--bar"
`shouldBe` Right [Wait, Print "foo", Wait, Wait, Print "bar"]
describe "Edge case" $ do
it "parses empty string ok" $ do
parseMbl ""
`shouldBe` Right []
describe "Escaped" $ do
it "can print the delimiter if escaped with \\ " $ do
parseMbl "--this is a\\-somewhat\\-convoluted example"
`shouldBe` Right [Wait, Wait, Print "this is a-somewhat-convoluted example"]

0 comments on commit c179930

Please sign in to comment.