module Expr (
Desc(..), mkDesc
, AnyExpr(..), AnyFunc(..)
, Expr(..), Func, params, name, hasVar
, hashWithName, hashList, hashString
, evalConst, isConst
, assertArgs1, assertArgs2
, mkBoolExpr, mkIntExpr, mkStringExpr, mkDoubleExpr, mkBytesExpr, mkUintExpr
, assertBool, assertInt, assertString, assertDouble, assertBytes, assertUint
, boolExpr, intExpr, stringExpr, doubleExpr, bytesExpr, uintExpr
, trimBool, trimInt, trimString, trimDouble, trimBytes, trimUint
, mkBoolsExpr, mkIntsExpr, mkStringsExpr, mkDoublesExpr, mkListOfBytesExpr, mkUintsExpr
, assertBools, assertInts, assertStrings, assertDoubles, assertListOfBytes, assertUints
, boolsExpr, intsExpr, stringsExpr, doublesExpr, listOfBytesExpr, uintsExpr
) where
import Data.Char (ord)
import Data.List (intercalate)
import Data.Text (Text, unpack, pack)
import Data.ByteString (ByteString)
import qualified Parsers
assertArgs1 :: String -> [AnyExpr] -> Either String AnyExpr
assertArgs1 _ [e1] = Right e1
assertArgs1 exprName es = Left $ exprName ++ ": expected one argument, but got " ++ show (length es) ++ ": " ++ show es
assertArgs2 :: String -> [AnyExpr] -> Either String (AnyExpr, AnyExpr)
assertArgs2 _ [e1, e2] = Right (e1, e2)
assertArgs2 exprName es = Left $ exprName ++ ": expected two arguments, but got " ++ show (length es) ++ ": " ++ show es
data Desc = Desc {
_name :: String
, _toStr :: String
, _hash :: Int
, _params :: [Desc]
, _hasVar :: Bool
}
mkDesc :: String -> [Desc] -> Desc
mkDesc n ps = Desc {
_name = n
, _toStr = n ++ "(" ++ intercalate "," (map show ps) ++ ")"
, _hash = hashWithName n ps
, _params = ps
, _hasVar = any _hasVar ps
}
instance Show Desc where
show = _toStr
instance Ord Desc where
compare = cmp
instance Eq Desc where
(==) a b = cmp a b == EQ
data AnyExpr = AnyExpr {
_desc :: Desc
, _eval :: AnyFunc
}
type Func a = (Parsers.Label -> Either String a)
instance Show AnyExpr where
show a = show (_desc a)
instance Eq AnyExpr where
(==) a b = _desc a == _desc b
instance Ord AnyExpr where
compare a b = cmp (_desc a) (_desc b)
data AnyFunc = BoolFunc (Func Bool)
| IntFunc (Func Int)
| StringFunc (Func Text)
| DoubleFunc (Func Double)
| UintFunc (Func Word)
| BytesFunc (Func ByteString)
| BoolsFunc (Func [Bool])
| IntsFunc (Func [Int])
| StringsFunc (Func [Text])
| DoublesFunc (Func [Double])
| UintsFunc (Func [Word])
| ListOfBytesFunc (Func [ByteString])
data Expr a = Expr {
desc :: Desc
, eval :: Func a
}
instance Show (Expr a) where
show e = show (desc e)
instance Eq (Expr a) where
(==) x y = desc x == desc y
instance Ord (Expr a) where
compare x y = cmp (desc x) (desc y)
params :: Expr a -> [Desc]
params = _params . desc
name :: Expr a -> String
name = _name . desc
hasVar :: Expr a -> Bool
hasVar = _hasVar . desc
mkBoolExpr :: Expr Bool -> AnyExpr
mkBoolExpr (Expr desc eval) = AnyExpr desc (BoolFunc eval)
assertBool :: AnyExpr -> Either String (Expr Bool)
assertBool (AnyExpr desc (BoolFunc eval)) = Right $ Expr desc eval
assertBool (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type bool"
mkIntExpr :: Expr Int -> AnyExpr
mkIntExpr (Expr desc eval) = AnyExpr desc (IntFunc eval)
assertInt :: AnyExpr -> Either String (Expr Int)
assertInt (AnyExpr desc (IntFunc eval)) = Right $ Expr desc eval
assertInt (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type int"
mkDoubleExpr :: Expr Double -> AnyExpr
mkDoubleExpr (Expr desc eval) = AnyExpr desc (DoubleFunc eval)
assertDouble :: AnyExpr -> Either String (Expr Double)
assertDouble (AnyExpr desc (DoubleFunc eval)) = Right $ Expr desc eval
assertDouble (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type double"
mkStringExpr :: Expr Text -> AnyExpr
mkStringExpr (Expr desc eval) = AnyExpr desc (StringFunc eval)
assertString :: AnyExpr -> Either String (Expr Text)
assertString (AnyExpr desc (StringFunc eval)) = Right $ Expr desc eval
assertString (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type string"
mkUintExpr :: Expr Word -> AnyExpr
mkUintExpr (Expr desc eval) = AnyExpr desc (UintFunc eval)
assertUint :: AnyExpr -> Either String (Expr Word)
assertUint (AnyExpr desc (UintFunc eval)) = Right $ Expr desc eval
assertUint (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type uint"
mkBytesExpr :: Expr ByteString -> AnyExpr
mkBytesExpr (Expr desc eval) = AnyExpr desc (BytesFunc eval)
assertBytes :: AnyExpr -> Either String (Expr ByteString)
assertBytes (AnyExpr desc (BytesFunc eval)) = Right $ Expr desc eval
assertBytes (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type bytes"
mkBoolsExpr :: Expr [Bool] -> AnyExpr
mkBoolsExpr (Expr desc eval) = AnyExpr desc (BoolsFunc eval)
assertBools :: AnyExpr -> Either String (Expr [Bool])
assertBools (AnyExpr desc (BoolsFunc eval)) = Right $ Expr desc eval
assertBools (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type bools"
mkIntsExpr :: Expr [Int] -> AnyExpr
mkIntsExpr (Expr desc eval) = AnyExpr desc (IntsFunc eval)
assertInts :: AnyExpr -> Either String (Expr [Int])
assertInts (AnyExpr desc (IntsFunc eval)) = Right $ Expr desc eval
assertInts (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type ints"
mkUintsExpr :: Expr [Word] -> AnyExpr
mkUintsExpr (Expr desc eval) = AnyExpr desc (UintsFunc eval)
assertUints :: AnyExpr -> Either String (Expr [Word])
assertUints (AnyExpr desc (UintsFunc eval)) = Right $ Expr desc eval
assertUints (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type uints"
mkDoublesExpr :: Expr [Double] -> AnyExpr
mkDoublesExpr (Expr desc eval) = AnyExpr desc (DoublesFunc eval)
assertDoubles :: AnyExpr -> Either String (Expr [Double])
assertDoubles (AnyExpr desc (DoublesFunc eval)) = Right $ Expr desc eval
assertDoubles (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type doubles"
mkStringsExpr :: Expr [Text] -> AnyExpr
mkStringsExpr (Expr desc eval) = AnyExpr desc (StringsFunc eval)
assertStrings :: AnyExpr -> Either String (Expr [Text])
assertStrings (AnyExpr desc (StringsFunc eval)) = Right $ Expr desc eval
assertStrings (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type strings"
mkListOfBytesExpr :: Expr [ByteString] -> AnyExpr
mkListOfBytesExpr (Expr desc eval) = AnyExpr desc (ListOfBytesFunc eval)
assertListOfBytes :: AnyExpr -> Either String (Expr [ByteString])
assertListOfBytes (AnyExpr desc (ListOfBytesFunc eval)) = Right $ Expr desc eval
assertListOfBytes (AnyExpr desc _) = Left $ "expected <" ++ show desc ++ "> to be of type bytes"
cmp :: Desc -> Desc -> Ordering
cmp a b = compare (_hash a) (_hash b) <>
compare (_name a) (_name b) <>
compare (length (_params a)) (length (_params b)) <>
foldl (<>) EQ (zipWith cmp (_params a) (_params b)) <>
compare (_toStr a) (_toStr b)
hashWithName :: String -> [Desc] -> Int
hashWithName s ds = hashList (31*17 + hashString s) (map _hash ds)
hashString :: String -> Int
hashString s = hashList 0 (map ord s)
hashList :: Int -> [Int] -> Int
hashList = foldl (\acc h -> 31*acc + h)
noLabel :: Parsers.Label
noLabel = Parsers.String (pack "not a label, trying constant evaluation")
evalConst :: Expr a -> Maybe a
evalConst e = if hasVar e
then Nothing
else case eval e noLabel of
(Left _) -> Nothing
(Right v) -> Just v
isConst :: Desc -> Bool
isConst d = not (null (_params d)) && case _name d of
"bool" -> True
"int" -> True
"uint" -> True
"double" -> True
"string" -> True
"[]byte" -> True
_ -> False
boolExpr :: Bool -> Expr Bool
boolExpr b = Expr {
desc = Desc {
_name = "bool"
, _toStr = if b then "true" else "false"
, _hash = if b then 3 else 5
, _params = []
, _hasVar = False
}
, eval = const $ return b
}
intExpr :: Int -> Expr Int
intExpr i = Expr {
desc = Desc {
_name = "int"
, _toStr = show i
, _hash = i
, _params = []
, _hasVar = False
}
, eval = const $ return i
}
doubleExpr :: Double -> Expr Double
doubleExpr d = Expr {
desc = Desc {
_name = "double"
, _toStr = show d
, _hash = truncate d
, _params = []
, _hasVar = False
}
, eval = const $ return d
}
uintExpr :: Word -> Expr Word
uintExpr i = Expr {
desc = Desc {
_name = "uint"
, _toStr = show i
, _hash = hashString (show i)
, _params = []
, _hasVar = False
}
, eval = const $ return i
}
stringExpr :: Text -> Expr Text
stringExpr s = Expr {
desc = Desc {
_name = "string"
, _toStr = show s
, _hash = hashString (unpack s)
, _params = []
, _hasVar = False
}
, eval = const $ return s
}
bytesExpr :: ByteString -> Expr ByteString
bytesExpr b = Expr {
desc = Desc {
_name = "bytes"
, _toStr = "[]byte{" ++ show b ++ "}"
, _hash = hashString (show b)
, _params = []
, _hasVar = False
}
, eval = const $ return b
}
trimBool :: Expr Bool -> Expr Bool
trimBool e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> boolExpr v
trimInt :: Expr Int -> Expr Int
trimInt e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> intExpr v
trimUint :: Expr Word -> Expr Word
trimUint e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> uintExpr v
trimString :: Expr Text -> Expr Text
trimString e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> stringExpr v
trimDouble :: Expr Double -> Expr Double
trimDouble e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> doubleExpr v
trimBytes :: Expr ByteString -> Expr ByteString
trimBytes e = if hasVar e
then e
else case eval e noLabel of
(Left _) -> e
(Right v) -> bytesExpr v
boolsExpr :: [Expr Bool] -> Expr [Bool]
boolsExpr = seqExprs "[]bool"
intsExpr :: [Expr Int] -> Expr [Int]
intsExpr = seqExprs "[]int"
stringsExpr :: [Expr Text] -> Expr [Text]
stringsExpr = seqExprs "[]string"
doublesExpr :: [Expr Double] -> Expr [Double]
doublesExpr = seqExprs "[]double"
listOfBytesExpr :: [Expr ByteString] -> Expr [ByteString]
listOfBytesExpr = seqExprs "[][]byte"
uintsExpr :: [Expr Word] -> Expr [Word]
uintsExpr = seqExprs "[]uint"
seqExprs :: String -> [Expr a] -> Expr [a]
seqExprs n es = Expr {
desc = mkDesc n (map desc es)
, eval = \v -> mapM (`eval` v) es
}