aboutsummaryrefslogtreecommitdiffstats
path: root/src/BizExpr.hs
blob: b11ffc18713477929f19cba10f7b648cf819b7b8 (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
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
{-# LANGUAGE FlexibleInstances #-}

module BizExpr (repl, eval, Context) where

import Data.Maybe (fromMaybe)
import Text.Read (readMaybe)
import qualified Data.Text.Lazy as L
import qualified Data.Map as M
import System.IO (isEOF)
import Control.Monad (when)

type Context = M.Map L.Text L.Text

repl :: IO ()
repl = do
  eof <- isEOF
  when (not eof) (
      getLine >>=
        putStrLn
        . maybe "Failed to evaluate expression" id
        . (eval M.empty :: String -> Maybe String)
      >> repl
    )

maybeHead (x:_) = Just x
maybeHead _ = Nothing

eval :: CoerceTo a => Context -> String -> Maybe a
eval c x = coerceTo =<< evalAst =<< maybeHead . fst =<< parseLevel c x

data Value = IntVal Integer | StrVal String | BoolVal Bool | FloatVal Float
  deriving (Show)

class CoerceTo a where
  coerceTo :: Value -> Maybe a
  coerceFrom :: a -> Value

instance CoerceTo Integer where
  coerceTo (FloatVal n) = Just $ floor n
  coerceTo (IntVal n) = Just n
  coerceTo v = coerceTo . FloatVal =<< coerceTo v
  coerceFrom = IntVal

instance CoerceTo Float where
  coerceTo (FloatVal n) = Just n
  coerceTo (IntVal n) = Just $ fromIntegral n
  coerceTo (StrVal s) = readMaybe s
  coerceTo (BoolVal True) = Just 1
  coerceTo (BoolVal False) = Just 0

  coerceFrom = FloatVal

instance CoerceTo String where
  coerceTo (BoolVal v) = Just $ show v
  coerceTo (IntVal v) = Just $ show v
  coerceTo (StrVal v) = Just v
  coerceTo (FloatVal v) = Just $ show v
  coerceFrom = StrVal

instance CoerceTo Bool where
  coerceTo (BoolVal v) = Just v
  coerceTo (IntVal v) = Just $ v /= 0
  coerceTo (StrVal "True") = Just True
  coerceTo (StrVal "true") = Just True
  coerceTo v = coerceTo . IntVal =<< coerceTo v

  coerceFrom = BoolVal

type Name = String

data Ast
  = Expr Name [Ast]
  | Val Value
  deriving (Show)

parseLevel :: Context -> String -> Maybe ([Ast], String)
parseLevel c = go "" (Just [])
  where
    go :: String -> Maybe [Ast] -> String -> Maybe ([Ast], String)
    go prev (Just l) ('(' : next) =
      case parseLevel c next of
        Nothing ->
          Nothing
        Just (arg, remnant) ->
          let r =
                if remnant /= "" && head remnant == ','
                  then tail remnant
                  else remnant
           in go "" (Just (l ++ [Expr prev arg])) r
    go prev (Just l) (')' : remnant) =
      let l0 = [Val $ newVal c prev | prev /= ""]
       in Just (l ++ l0, remnant)
    go prev (Just l) (',' : next) =
      let l0 = [Val $ newVal c prev]
       in go "" (Just (l ++ l0)) next
    go prev l (' ' : next) =
      go "" l next
    go "" (Just l) "" =
      Just (l, "")
    go prev (Just l) "" =
      Just (l ++ [Val $ newVal c prev], "")
    go prev l (x : xs) =
      go (prev ++ [x]) l xs

newVal :: Context -> String -> Value
newVal c x = case M.lookup (L.pack x) c of
  Nothing -> StrVal x
  Just n -> StrVal $ L.unpack n

evalAst :: Ast -> Maybe Value
evalAst (Expr name ast) = fromMaybe Nothing (getFunc name <*> evalLevel ast)
evalAst (Val val) = Just val

evalLevel :: [Ast] -> Maybe [Value]
evalLevel = mapM evalAst

getFunc :: String -> Maybe ([Value] -> Maybe Value)
getFunc "sum" = Just eSum
getFunc "any" = Just eAny
getFunc "all" = Just eAll
getFunc "average" = Just eAverage
getFunc _ = Nothing

eSum :: [Value] -> Maybe Value
eSum = eFold (+) (0.0 :: Float)

eAny :: [Value] -> Maybe Value
eAny = eFold (||) False

eAll :: [Value] -> Maybe Value
eAll = eFold (&&) True

eAverage :: [Value] -> Maybe Value
eAverage xs = do
  let n = coerceTo =<< eSum xs
      d = Just . fromIntegral $ length xs
   in FloatVal <$> ((/) <$> n <*> d)

eFold :: (CoerceTo a, CoerceTo b) => (b -> a -> b) -> b -> [Value] -> Maybe Value
eFold fn init [] = Just $ coerceFrom init
eFold fn init (x : xs) =
  let b = coerceTo =<< eFold fn init xs
      a = coerceTo x
   in coerceFrom <$> (fn <$> b <*> a)