Skip to content

Commit

Permalink
Introduce a State Monad for the generators
Browse files Browse the repository at this point in the history
  • Loading branch information
mfussenegger committed Nov 30, 2018
1 parent 1b2c22b commit f1d9941
Show file tree
Hide file tree
Showing 3 changed files with 56 additions and 26 deletions.
73 changes: 47 additions & 26 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,24 +2,32 @@

module Main where

import Control.Monad (forever)
import Data.Aeson (Value (..), encode, object)
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Either (isRight, lefts)
import Data.Maybe (fromJust, mapMaybe)
import qualified Data.Scientific as S
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Read as T
import qualified Data.UUID as UUID
import qualified Data.UUID.V1 as UUID1
import qualified Data.UUID.V4 as UUID4
import Expr (Expr (..), parseExpr)
import System.Environment (getArgs)
import System.Random (getStdGen, randomR, setStdGen)

import Control.Monad (forever)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State.Strict (StateT)
import qualified Control.Monad.Trans.State.Strict as State
import Data.Aeson (Value (..), encode, object)
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Either (isRight, lefts)
import Data.Maybe (fromJust, mapMaybe)
import qualified Data.Scientific as S
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Read as T
import qualified Data.UUID as UUID
import qualified Data.UUID.V1 as UUID1
import Expr (Expr (..), parseExpr)
import System.Environment (getArgs)
import System.Random (StdGen, newStdGen, random,
randomR)

-- $setup
-- >>> :set -XOverloadedStrings
-- >>> import System.Random (mkStdGen)

type State a = StateT StdGen IO a


parseColumnDefinition :: String -> Maybe (Text, Text)
parseColumnDefinition x =
Expand All @@ -31,9 +39,9 @@ parseColumnDefinition x =
parts = T.splitOn "=" text


uuid1 :: IO UUID.UUID
uuid1 :: State UUID.UUID
uuid1 = do
uuid <- UUID1.nextUUID
uuid <- liftIO UUID1.nextUUID
case uuid of
(Just u) -> pure u
Nothing -> uuid1
Expand Down Expand Up @@ -61,36 +69,49 @@ asInt o = error $ "Expected an integer but received: " <> show o

-- | Create a value getter for an expression
--
-- >>> eval $ FunctionCall "randomInt" [IntLiteral 1, IntLiteral 1]
-- Number 1.0
eval :: Expr -> IO Value
-- >>> State.evalStateT (eval "randomInt(1, 2)") (mkStdGen 1)
-- Number 2.0
--
-- >>> State.evalStateT (eval "uuid4") (mkStdGen 1)
-- String "0099a82c-36f7-4321-8012-daa4305fd84b"
eval :: Expr -> State Value
eval (IntLiteral x) = pure $ Number $ fromInteger x
eval (StringLiteral x) = pure $ String x
eval (FunctionCall "uuid4" []) = String . UUID.toText <$> UUID4.nextRandom
eval (FunctionCall "uuid4" []) = do
stdGen <- State.get
let
(uuid, newGen) = random stdGen
State.put newGen
pure $ String $ UUID.toText uuid
eval (FunctionCall "uuid1" []) = String . UUID.toText <$> uuid1
eval (FunctionCall "randomInt" [lower, upper]) = do
lower' <- asInt <$> eval lower
upper' <- asInt <$> eval upper
stdGen <- getStdGen
stdGen <- State.get
let
(rndNumber, newStdGen) = randomR (lower', upper') stdGen
setStdGen newStdGen
(rndNumber, newGen) = randomR (lower', upper') stdGen
State.put newGen
pure $ Number $ fromIntegral rndNumber
eval (FunctionCall name _) = pure $ String $ "No random generator for " <> name


main :: IO ()
main = do
args <- getArgs
stdGen <- newStdGen
let
columns = mapMaybe parseColumnDefinition args
allExpressions = fmap (\(x, y) -> (x, parseExpr y)) columns
expressions = fmap unpackRight (filter (isRight . snd) allExpressions)
errored = lefts $ fmap snd allExpressions
providers = fmap (\(x, y) -> (x, eval y)) expressions
if null errored
then forever $
mapM runProvider providers >>= BL.putStrLn . encode . object
then
let
printRecords = forever $
mapM runProvider providers >>= liftIO . BL.putStrLn . encode . object
in
State.runStateT printRecords stdGen >> pure ()
else
mapM_ print errored
where
Expand Down
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ dependencies:
- parsec
- random
- scientific
- transformers

library:
source-dirs: src
Expand Down
8 changes: 8 additions & 0 deletions src/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
module Expr where

import Data.Maybe (fromMaybe)
import Data.String (IsString(..))
import Data.Text (Text)
import qualified Data.Text as T
import Text.Parsec (many, many1, optionMaybe, parse, sepBy,
Expand All @@ -19,6 +20,13 @@ data Expr = IntLiteral Integer
| FunctionCall { fcName :: Text, fcArgs :: [Expr] }
deriving (Show, Eq)


instance IsString Expr where
fromString s =
case parseExpr (T.pack s) of
(Left err) -> error $ show err
(Right e) -> e

expr :: Parser Expr
expr = literal <|> functionCall

Expand Down

0 comments on commit f1d9941

Please sign in to comment.