summaryrefslogtreecommitdiff
path: root/src/Test.hs
blob: 16c1b1f977536f05d0e77bf60f0b8ae5abb90067 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
module Test (
    Test(..),
    TestStep(..),
    SourceLine(..),

    ProcName(..), textProcName, unpackProcName,
    NodeName(..), textNodeName, unpackNodeName,

    MonadEval(..),
    VarName(..), textVarName, unpackVarName,
    ExprType(..),
    SomeVarValue(..), fromSomeVarValue, textSomeVarValue,
    Expr(..), eval, gatherVars,
    Regex,
) where

import Control.Monad

import Data.Char
import Data.List
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable

import Text.Regex.TDFA
import Text.Regex.TDFA.Text

import Process
import Util

data Test = Test
    { testName :: Text
    , testSteps :: [TestStep]
    }

data TestStep = forall a. ExprType a => Let SourceLine VarName (Expr a)
              | Spawn ProcName NodeName
              | Send ProcName (Expr Text)
              | Expect SourceLine ProcName (Expr Regex) [VarName]
              | Guard SourceLine (Expr Bool)
              | Wait

newtype SourceLine = SourceLine Text

newtype NodeName = NodeName Text
    deriving (Eq, Ord)

textNodeName :: NodeName -> Text
textNodeName (NodeName name) = name

unpackNodeName :: NodeName -> String
unpackNodeName (NodeName tname) = T.unpack tname


class MonadFail m => MonadEval m where
  lookupVar :: VarName -> m SomeVarValue


data VarName = VarName [Text]
    deriving (Eq, Ord)

textVarName :: VarName -> Text
textVarName (VarName name) = T.concat $ intersperse (T.singleton '.') name

unpackVarName :: VarName -> String
unpackVarName = T.unpack . textVarName


class Typeable a => ExprType a where
  textExprType :: proxy a -> Text
  textExprValue :: a -> Text
  emptyVarValue :: a

instance ExprType Integer where
  textExprType _ = T.pack "integer"
  textExprValue x = T.pack (show x)
  emptyVarValue = 0

instance ExprType Text where
  textExprType _ = T.pack "string"
  textExprValue x = T.pack (show x)
  emptyVarValue = T.empty

data SomeVarValue = forall a. ExprType a => SomeVarValue a

fromSomeVarValue :: forall a m. (ExprType a, MonadFail m) => VarName -> SomeVarValue -> m a
fromSomeVarValue name (SomeVarValue value) = maybe (fail err) return $ cast value
  where err = T.unpack $ T.concat [ T.pack "expected ", textExprType @a Proxy, T.pack ", but variable '", textVarName name, T.pack "' has type ", textExprType (Just value) ]

textSomeVarValue :: SomeVarValue -> Text
textSomeVarValue (SomeVarValue value) = textExprValue value


data Expr a where
    Variable :: ExprType a => VarName -> Expr a
    Literal :: ExprType a => a -> Expr a
    Concat :: [Expr Text] -> Expr Text
    Regex :: [Expr Text] -> Expr Regex
    BinOp :: (b -> c -> a) -> Expr b -> Expr c -> Expr a

eval :: MonadEval m => Expr a -> m a
eval (Variable name) = fromSomeVarValue name =<< lookupVar name
eval (Literal value) = return value
eval (Concat xs) = T.concat <$> mapM eval xs
eval (Regex xs) = do
    parts <- forM xs $ \case
        Literal value | Just str <- cast value -> return str
                      | otherwise -> fail $ "regex expansion not defined for " ++ T.unpack (textExprType $ Just value)
        expr -> T.concatMap escapeChar <$> eval expr
          where
            escapeChar c | isAlphaNum c = T.singleton c
                         | c `elem` "`'<>" = T.singleton c
                         | otherwise = T.pack ['\\', c]
    case compile defaultCompOpt defaultExecOpt $ T.concat $ concat [[T.singleton '^'], parts, [T.singleton '$']] of
        Left err -> fail err
        Right re -> return re
eval (BinOp f x y) = f <$> eval x <*> eval y

gatherVars :: forall a m. MonadEval m => Expr a -> m [(VarName, SomeVarValue)]
gatherVars = fmap (uniqOn fst . sortOn fst) . helper
  where
    helper :: forall b. Expr b -> m [(VarName, SomeVarValue)]
    helper (Variable var) = (:[]) . (var,) <$> lookupVar var
    helper (Literal _) = return []
    helper (Concat es) = concat <$> mapM helper es
    helper (Regex es) = concat <$> mapM helper es
    helper (BinOp _ e f) = (++) <$> helper e <*> helper f