{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Recalc.EngineSpec where
import Control.Monad (void)
import Control.Monad.Reader
import Data.Char (isAlphaNum)
import Data.List (foldl', sortOn)
import Data.Maybe (mapMaybe)
import Data.Set (Set)
import Data.Set qualified as Set
import Data.String (IsString (..))
import Data.Text qualified as Text
import Data.Void (Void)
import Network.URI (parseURI)
import Prettyprinter hiding (column)
import Test.Hspec (Spec, describe, it, shouldBe)
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Char.Lexer (decimal)
import Recalc.Engine hiding (newEngineState, recalc)
import Recalc.Repl (newEngineState, recalc)
instance IsString (Maybe String) where
fromString :: String -> Maybe String
fromString = \case String
"" -> Maybe String
forall a. Maybe a
Nothing; String
str -> String -> Maybe String
forall a. a -> Maybe a
Just String
str
type Result = Either (FetchError ())
run :: [[(CellAddr, Maybe String)]] -> (ResultsOf Term, EngineStateOf Term)
run :: [[(CellAddr, Maybe String)]]
-> (ResultsOf Term, EngineStateOf Term)
run = (([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellAddr, Maybe String)]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int))
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [[(CellAddr, Maybe String)]]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellAddr, Maybe String)]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
forall {a}.
(a, EngineState () () Term () Term Int)
-> [(CellAddr, Maybe String)]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
alg (String -> [(CellRef, Cell () Term () Term Int)]
forall a. HasCallStack => String -> a
error String
"no inputs", EnvOf Term -> EngineStateOf Term
forall t. EnvOf t -> EngineStateOf t
newEngineState ())
where
alg :: (a, EngineState () () Term () Term Int)
-> [(CellAddr, Maybe String)]
-> (ResultsOf Term, EngineStateOf Term)
alg (a
_, EngineState () () Term () Term Int
st) [(CellAddr, Maybe String)]
inputs = forall t.
(Recalc t, Show (ErrorOf t)) =>
[(CellAddr, Maybe String)]
-> EngineStateOf t -> (ResultsOf t, EngineStateOf t)
recalc @Term [(CellAddr, Maybe String)]
inputs EngineState () () Term () Term Int
EngineStateOf Term
st
evalSheet :: [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet :: [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet =
((CellAddr, Int) -> CellAddr)
-> [(CellAddr, Int)] -> [(CellAddr, Int)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (CellAddr, Int) -> CellAddr
forall a b. (a, b) -> a
fst
([(CellAddr, Int)] -> [(CellAddr, Int)])
-> ([[(CellAddr, Maybe String)]] -> [(CellAddr, Int)])
-> [[(CellAddr, Maybe String)]]
-> [(CellAddr, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((CellRef, Cell () Term () Term Int) -> Maybe (CellAddr, Int))
-> [(CellRef, Cell () Term () Term Int)] -> [(CellAddr, Int)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\((SheetId
_, CellAddr
ca), Cell () Term () Term Int
c) -> (Int -> (CellAddr, Int)) -> Maybe Int -> Maybe (CellAddr, Int)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CellAddr
ca,) (Maybe Int -> Maybe (CellAddr, Int))
-> ((((), Term), Maybe Int) -> Maybe Int)
-> (((), Term), Maybe Int)
-> Maybe (CellAddr, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((), Term), Maybe Int) -> Maybe Int
forall a b. (a, b) -> b
snd ((((), Term), Maybe Int) -> Maybe (CellAddr, Int))
-> Maybe (((), Term), Maybe Int) -> Maybe (CellAddr, Int)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Term, Maybe (((), Term), Maybe Int))
-> Maybe (((), Term), Maybe Int)
forall a b. (a, b) -> b
snd ((Term, Maybe (((), Term), Maybe Int))
-> Maybe (((), Term), Maybe Int))
-> Maybe (Term, Maybe (((), Term), Maybe Int))
-> Maybe (((), Term), Maybe Int)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
-> Maybe (Term, Maybe (((), Term), Maybe Int))
forall a b. (a, b) -> b
snd (((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
-> Maybe (Term, Maybe (((), Term), Maybe Int)))
-> Maybe
((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
-> Maybe (Term, Maybe (((), Term), Maybe Int))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Cell () Term () Term Int
-> Maybe
((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
forall err f t e v.
Cell err f t e v
-> Maybe ((String, CellType), Maybe (f, Maybe ((t, e), Maybe v)))
cell Cell () Term () Term Int
c)
([(CellRef, Cell () Term () Term Int)] -> [(CellAddr, Int)])
-> ([[(CellAddr, Maybe String)]]
-> [(CellRef, Cell () Term () Term Int)])
-> [[(CellAddr, Maybe String)]]
-> [(CellAddr, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellRef, Cell () Term () Term Int)]
forall a b. (a, b) -> a
fst
(([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellRef, Cell () Term () Term Int)])
-> ([[(CellAddr, Maybe String)]]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int))
-> [[(CellAddr, Maybe String)]]
-> [(CellRef, Cell () Term () Term Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(CellAddr, Maybe String)]]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
[[(CellAddr, Maybe String)]]
-> (ResultsOf Term, EngineStateOf Term)
run
evalSheetKeepErrors :: [[(CellAddr, Maybe String)]] -> [(CellAddr, Result Int)]
evalSheetKeepErrors :: [[(CellAddr, Maybe String)]] -> [(CellAddr, Result Int)]
evalSheetKeepErrors =
((CellAddr, Result Int) -> CellAddr)
-> [(CellAddr, Result Int)] -> [(CellAddr, Result Int)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (CellAddr, Result Int) -> CellAddr
forall a b. (a, b) -> a
fst
([(CellAddr, Result Int)] -> [(CellAddr, Result Int)])
-> ([[(CellAddr, Maybe String)]] -> [(CellAddr, Result Int)])
-> [[(CellAddr, Maybe String)]]
-> [(CellAddr, Result Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((CellRef, Cell () Term () Term Int) -> (CellAddr, Result Int))
-> [(CellRef, Cell () Term () Term Int)]
-> [(CellAddr, Result Int)]
forall a b. (a -> b) -> [a] -> [b]
map (\((SheetId
_, CellAddr
ca), Cell () Term () Term Int
x) -> (CellAddr
ca, CellOf Term -> Result Int
unpack Cell () Term () Term Int
CellOf Term
x))
([(CellRef, Cell () Term () Term Int)] -> [(CellAddr, Result Int)])
-> ([[(CellAddr, Maybe String)]]
-> [(CellRef, Cell () Term () Term Int)])
-> [[(CellAddr, Maybe String)]]
-> [(CellAddr, Result Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellRef, Cell () Term () Term Int)]
forall a b. (a, b) -> a
fst
(([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
-> [(CellRef, Cell () Term () Term Int)])
-> ([[(CellAddr, Maybe String)]]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int))
-> [[(CellAddr, Maybe String)]]
-> [(CellRef, Cell () Term () Term Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(CellAddr, Maybe String)]]
-> ([(CellRef, Cell () Term () Term Int)],
EngineState () () Term () Term Int)
[[(CellAddr, Maybe String)]]
-> (ResultsOf Term, EngineStateOf Term)
run
where
unpack :: CellOf Term -> Result Int
unpack :: CellOf Term -> Result Int
unpack CellOf Term
c = case (Cell () Term () Term Int
-> Maybe
((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
forall err f t e v.
Cell err f t e v
-> Maybe ((String, CellType), Maybe (f, Maybe ((t, e), Maybe v)))
cell Cell () Term () Term Int
CellOf Term
c, Cell () Term () Term Int -> Maybe (FetchError ())
forall err f t e v. Cell err f t e v -> Maybe (FetchError err)
cellError Cell () Term () Term Int
CellOf Term
c) of
(Maybe
((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int)))
_, Just FetchError ()
err) -> FetchError () -> Result Int
forall a b. a -> Either a b
Left FetchError ()
err
(Just ((String, CellType)
_, Just (Term
_, Just (((), Term)
_, Just Int
q))), Maybe (FetchError ())
_) -> Int -> Result Int
forall a b. b -> Either a b
Right Int
q
(Maybe
((String, CellType), Maybe (Term, Maybe (((), Term), Maybe Int))),
Maybe (FetchError ()))
_ -> FetchError () -> Result Int
forall a b. a -> Either a b
Left FetchError ()
forall err. FetchError err
RefError
spec :: Spec
spec :: Spec
spec = do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"sheet arithmetics" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"reacts on new values entered"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet [[((Int
2, Int
2), Maybe String
"12"), ((Int
0, Int
0), Maybe String
"=1+2"), ((Int
1, Int
1), Maybe String
"=0")]]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [ ((Int
0, Int
0), Int
3)
, ((Int
1, Int
1), Int
0)
, ((Int
2, Int
2), Int
12)
]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"computes handles simple refs" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ do
[[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet [[((Int
1, Int
0), Maybe String
"1")], [((Int
2, Int
2), Maybe String
"=A2")]] [(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
2, Int
2), Int
1)]
[[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet [[((Int
0, Int
0), Maybe String
"=1+1")], [((Int
2, Int
2), Maybe String
"=A1")]] [(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
2, Int
2), Int
2)]
[[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet [[((Int
5, Int
3), Maybe String
"8")], [((Int
2, Int
2), Maybe String
"=D6")]] [(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
2, Int
2), Int
8)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"computes sum of previously entered values"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet
[ [((Int
0, Int
1), Maybe String
"12"), ((Int
1, Int
0), Maybe String
"2"), ((Int
0, Int
0), Maybe String
"=1+2"), ((Int
1, Int
1), Maybe String
"=1")]
, [((Int
2, Int
2), Maybe String
"=SUM(A1:B2)")]
]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
2, Int
2), Int
18)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"updates sum when value is changed (1)"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet
[ [((Int
0, Int
1), Maybe String
"12"), ((Int
1, Int
0), Maybe String
"2"), ((Int
0, Int
0), Maybe String
"=1+2"), ((Int
1, Int
1), Maybe String
"=1")]
, [((Int
2, Int
2), Maybe String
"=SUM(A1:B2)")]
, [((Int
0, Int
1), Maybe String
"0")]
]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
0, Int
1), Int
0), ((Int
2, Int
2), Int
6)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"updates sum when value is changed (2)"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet
[ [((Int
0, Int
1), Maybe String
"12"), ((Int
1, Int
0), Maybe String
"2"), ((Int
0, Int
0), Maybe String
"=1+2"), ((Int
1, Int
1), Maybe String
"=1")]
, [((Int
2, Int
2), Maybe String
"=SUM(A1:B2)")]
, [((Int
0, Int
0), Maybe String
"101")]
, [((Int
0, Int
1), Maybe String
"0")]
, [((Int
1, Int
0), Maybe String
"0")]
, [((Int
0, Int
0), Maybe String
"0")]
, [((Int
1, Int
1), Maybe String
"0")]
]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
1, Int
1), Int
0), ((Int
2, Int
2), Int
0)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"sum behaves with negative numbers"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet
[ [((Int
0, Int
1), Maybe String
"12"), ((Int
1, Int
0), Maybe String
"-2"), ((Int
0, Int
0), Maybe String
"=1+2"), ((Int
1, Int
1), Maybe String
"=1")]
, [((Int
2, Int
2), Maybe String
"=SUM(A1:B2)")]
, [((Int
0, Int
1), Maybe String
"0")]
]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
0, Int
1), Int
0), ((Int
2, Int
2), Int
2)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"gives a reference error when a referenced cell is deleted"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Result Int)]
evalSheetKeepErrors
[ [((Int
0, Int
1), String -> Maybe String
forall a. a -> Maybe a
Just String
"12")]
, [((Int
2, Int
2), String -> Maybe String
forall a. a -> Maybe a
Just String
"=B1")]
, [((Int
0, Int
1), Maybe String
forall a. Maybe a
Nothing)]
]
[(CellAddr, Result Int)] -> [(CellAddr, Result Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
2, Int
2), FetchError () -> Result Int
forall a b. a -> Either a b
Left FetchError ()
forall err. FetchError err
RefError)]
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"gives a reference error when a referenced cell is deleted"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Int)]
evalSheet
[ [((Int
0, Int
1), String -> Maybe String
forall a. a -> Maybe a
Just String
"12")]
, [((Int
2, Int
2), String -> Maybe String
forall a. a -> Maybe a
Just String
"=B1")]
, [((Int
0, Int
1), Maybe String
forall a. Maybe a
Nothing)]
, [((Int
0, Int
1), String -> Maybe String
forall a. a -> Maybe a
Just String
"42")]
]
[(CellAddr, Int)] -> [(CellAddr, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
0, Int
1), Int
42), ((Int
2, Int
2), Int
42)]
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"elaboration" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"passes funky test (elaborate error term to 42)"
(Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$ [[(CellAddr, Maybe String)]] -> [(CellAddr, Result Int)]
evalSheetKeepErrors [[((Int
0, Int
0), Maybe String
"=funky")]]
[(CellAddr, Result Int)] -> [(CellAddr, Result Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [((Int
0, Int
0), Int -> Result Int
forall a b. b -> Either a b
Right Int
42)]
data SheetRef
= Explicit {SheetRef -> SheetId
sheetId :: SheetId}
| Implicit {sheetId :: SheetId}
deriving (Int -> SheetRef -> ShowS
[SheetRef] -> ShowS
SheetRef -> String
(Int -> SheetRef -> ShowS)
-> (SheetRef -> String) -> ([SheetRef] -> ShowS) -> Show SheetRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SheetRef -> ShowS
showsPrec :: Int -> SheetRef -> ShowS
$cshow :: SheetRef -> String
show :: SheetRef -> String
$cshowList :: [SheetRef] -> ShowS
showList :: [SheetRef] -> ShowS
Show)
instance Pretty SheetRef where
pretty :: forall ann. SheetRef -> Doc ann
pretty = \case
Explicit (URI
uri, Text
sheetName) -> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (URI -> String
forall a. Show a => a -> String
show URI
uri String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"#" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
sheetName)
SheetRef
_ -> Doc ann
""
data Term
= Num Int
| Add Term Term
| Ref SheetRef CellAddr
| Sum SheetRef CellRange
| Funky
deriving (Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
(Int -> Term -> ShowS)
-> (Term -> String) -> ([Term] -> ShowS) -> Show Term
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Term -> ShowS
showsPrec :: Int -> Term -> ShowS
$cshow :: Term -> String
show :: Term -> String
$cshowList :: [Term] -> ShowS
showList :: [Term] -> ShowS
Show)
instance Pretty Term where
pretty :: forall ann. Term -> Doc ann
pretty = \case
Num Int
i -> Int -> Doc ann
forall ann. Int -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Int
i
Add Term
x Term
y -> Term -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Term -> Doc ann
pretty Term
x Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"+" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Term -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Term -> Doc ann
pretty Term
y
Ref SheetRef
_ CellAddr
ca -> String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CellAddr -> String
showExcel26 CellAddr
ca)
Sum SheetRef
_ (CellAddr
begin, CellAddr
end) ->
Doc ann
"sum"
Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
parens (String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ CellAddr -> String
showExcel26 CellAddr
begin String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CellAddr -> String
showExcel26 CellAddr
end)
Term
Funky -> Doc ann
"funky"
type Parser = ReaderT SheetId (Parsec Void String)
formulaP :: Parser Term
formulaP :: Parser Term
formulaP = Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'=' ReaderT SheetId (Parsec Void String) Char
-> Parser Term -> Parser Term
forall a b.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Term
termP
where
termP :: Parser Term
termP = do
Term
t <- [Parser Term] -> Parser Term
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice [Parser Term
valueP, Parser Term
funkyP, Parser Term -> Parser Term
forall a.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) a
forall e s (m :: * -> *) a. MonadParsec e s m => m a -> m a
try Parser Term
sumP, Parser Term
refP]
Term -> Parser Term -> Parser Term
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Term
t (Term -> Term -> Term
Add Term
t (Term -> Term) -> Parser Term -> Parser Term
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'+' ReaderT SheetId (Parsec Void String) Char
-> Parser Term -> Parser Term
forall a b.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Term
termP))
refP :: Parser Term
refP = SheetRef -> CellAddr -> Term
Ref (SheetRef -> CellAddr -> Term)
-> ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) (CellAddr -> Term)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT SheetId (Parsec Void String) SheetRef
sheetIdP ReaderT SheetId (Parsec Void String) (CellAddr -> Term)
-> ReaderT SheetId (Parsec Void String) CellAddr -> Parser Term
forall a b.
ReaderT SheetId (Parsec Void String) (a -> b)
-> ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT SheetId (Parsec Void String) CellAddr
cellAddrP
funkyP :: Parser Term
funkyP = Term
Funky Term
-> ReaderT SheetId (Parsec Void String) (Tokens String)
-> Parser Term
forall a b.
a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Tokens String
-> ReaderT SheetId (Parsec Void String) (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens String
"funky"
sumP :: Parser Term
sumP = do
ReaderT SheetId (Parsec Void String) (Tokens String)
-> ReaderT SheetId (Parsec Void String) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Tokens String
-> ReaderT SheetId (Parsec Void String) (Tokens String)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens String
"SUM")
ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) Char
-> Parser Term
-> Parser Term
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'(') (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
')')
(Parser Term -> Parser Term) -> Parser Term -> Parser Term
forall a b. (a -> b) -> a -> b
$ SheetRef -> CellRange -> Term
Sum (SheetRef -> CellRange -> Term)
-> ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) (CellRange -> Term)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT SheetId (Parsec Void String) SheetRef
sheetIdP ReaderT SheetId (Parsec Void String) (CellRange -> Term)
-> ReaderT SheetId (Parsec Void String) CellRange -> Parser Term
forall a b.
ReaderT SheetId (Parsec Void String) (a -> b)
-> ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT SheetId (Parsec Void String) CellRange
cellRangeP
sheetIdP :: ReaderT SheetId (Parsec Void String) SheetRef
sheetIdP =
[ReaderT SheetId (Parsec Void String) SheetRef]
-> ReaderT SheetId (Parsec Void String) SheetRef
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice
[ (ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) SheetRef
forall a b.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'!') (ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef)
-> (ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef)
-> ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef
forall (m :: * -> *) open close a.
Applicative m =>
m open -> m close -> m a -> m a
between (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'[') (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
']') (ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef)
-> ReaderT SheetId (Parsec Void String) SheetRef
-> ReaderT SheetId (Parsec Void String) SheetRef
forall a b. (a -> b) -> a -> b
$ do
let legalChar :: ReaderT SheetId (Parsec Void String) (Token String)
legalChar = (Token String -> Bool)
-> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
MonadParsec e s m =>
(Token s -> Bool) -> m (Token s)
satisfy (\Token String
c -> Char -> Bool
isAlphaNum Char
Token String
c Bool -> Bool -> Bool
|| Char
Token String
c Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"-./~" :: String))
String
path <- ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) String
forall {f :: * -> *} {a}. MonadPlus f => f a -> f [a]
many1 ReaderT SheetId (Parsec Void String) Char
ReaderT SheetId (Parsec Void String) (Token String)
legalChar
URI
uri <- ReaderT SheetId (Parsec Void String) URI
-> (URI -> ReaderT SheetId (Parsec Void String) URI)
-> Maybe URI
-> ReaderT SheetId (Parsec Void String) URI
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> ReaderT SheetId (Parsec Void String) URI
forall a. String -> ReaderT SheetId (Parsec Void String) a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid URI") URI -> ReaderT SheetId (Parsec Void String) URI
forall a. a -> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Maybe URI
parseURI (String
"file://" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path))
String
sheetName <- Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'#' ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) String
-> ReaderT SheetId (Parsec Void String) String
forall a b.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) String
forall {f :: * -> *} {a}. MonadPlus f => f a -> f [a]
many1 ReaderT SheetId (Parsec Void String) Char
ReaderT SheetId (Parsec Void String) (Token String)
legalChar
SheetRef -> ReaderT SheetId (Parsec Void String) SheetRef
forall a. a -> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SheetRef -> ReaderT SheetId (Parsec Void String) SheetRef)
-> SheetRef -> ReaderT SheetId (Parsec Void String) SheetRef
forall a b. (a -> b) -> a -> b
$ SheetId -> SheetRef
Explicit (URI
uri, String -> Text
Text.pack String
sheetName)
, (SheetId -> SheetRef)
-> ReaderT SheetId (Parsec Void String) SheetRef
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks SheetId -> SheetRef
Implicit
]
cellAddrP :: ReaderT SheetId (Parsec Void String) CellAddr
cellAddrP = do
String
colStr <- ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) String
forall {f :: * -> *} {a}. MonadPlus f => f a -> f [a]
many1 ReaderT SheetId (Parsec Void String) Char
ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
m (Token s)
upperChar
Int
rowDigits <- ReaderT SheetId (Parsec Void String) Int
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal
ReaderT SheetId (Parsec Void String) CellAddr
-> (CellAddr -> ReaderT SheetId (Parsec Void String) CellAddr)
-> Maybe CellAddr
-> ReaderT SheetId (Parsec Void String) CellAddr
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> ReaderT SheetId (Parsec Void String) CellAddr
forall a. String -> ReaderT SheetId (Parsec Void String) a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid cell reference") CellAddr -> ReaderT SheetId (Parsec Void String) CellAddr
forall a. a -> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe CellAddr -> ReaderT SheetId (Parsec Void String) CellAddr)
-> (Text -> Maybe CellAddr)
-> Text
-> ReaderT SheetId (Parsec Void String) CellAddr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe CellAddr
readExcel
(Text -> ReaderT SheetId (Parsec Void String) CellAddr)
-> Text -> ReaderT SheetId (Parsec Void String) CellAddr
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack (String
colStr String -> ShowS
forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show @Int Int
rowDigits)
cellRangeP :: ReaderT SheetId (Parsec Void String) CellRange
cellRangeP = (,) (CellAddr -> CellAddr -> CellRange)
-> ReaderT SheetId (Parsec Void String) CellAddr
-> ReaderT SheetId (Parsec Void String) (CellAddr -> CellRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT SheetId (Parsec Void String) CellAddr
cellAddrP ReaderT SheetId (Parsec Void String) (CellAddr -> CellRange)
-> ReaderT SheetId (Parsec Void String) CellAddr
-> ReaderT SheetId (Parsec Void String) CellRange
forall a b.
ReaderT SheetId (Parsec Void String) (a -> b)
-> ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
':' ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) CellAddr
-> ReaderT SheetId (Parsec Void String) CellAddr
forall a b.
ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ReaderT SheetId (Parsec Void String) CellAddr
cellAddrP)
many1 :: f a -> f [a]
many1 f a
p = (:) (a -> [a] -> [a]) -> f a -> f ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
p f ([a] -> [a]) -> f [a] -> f [a]
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f a -> f [a]
forall {f :: * -> *} {a}. MonadPlus f => f a -> f [a]
many f a
p
valueP :: Parser Term
valueP :: Parser Term
valueP = Int -> Term
Num (Int -> Term)
-> ReaderT SheetId (Parsec Void String) Int -> Parser Term
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Int -> Int)
-> ReaderT SheetId (Parsec Void String) (Int -> Int)
-> ReaderT SheetId (Parsec Void String) (Int -> Int)
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
option Int -> Int
forall a. a -> a
id (Int -> Int
forall a. Num a => a -> a
negate (Int -> Int)
-> ReaderT SheetId (Parsec Void String) Char
-> ReaderT SheetId (Parsec Void String) (Int -> Int)
forall a b.
a
-> ReaderT SheetId (Parsec Void String) b
-> ReaderT SheetId (Parsec Void String) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Token String -> ReaderT SheetId (Parsec Void String) (Token String)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token String
'-') ReaderT SheetId (Parsec Void String) (Int -> Int)
-> ReaderT SheetId (Parsec Void String) Int
-> ReaderT SheetId (Parsec Void String) Int
forall a b.
ReaderT SheetId (Parsec Void String) (a -> b)
-> ReaderT SheetId (Parsec Void String) a
-> ReaderT SheetId (Parsec Void String) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT SheetId (Parsec Void String) Int
forall e s (m :: * -> *) a.
(MonadParsec e s m, Token s ~ Char, Num a) =>
m a
decimal)
instance Recalc Term where
type EnvOf Term = ()
type ErrorOf Term = ()
type TypeOf Term = ()
type ValueOf Term = Int
parseCell :: CellType -> Parser Term
parseCell :: CellType -> Parser Term
parseCell = \case
CellType
CellFormula -> Parser Term
formulaP
CellType
CellValue -> Parser Term
valueP
depsOf :: Term -> Set CellRangeRef
depsOf :: Term -> Set CellRangeRef
depsOf = \case
Add Term
x Term
y -> (Term -> Set CellRangeRef) -> [Term] -> Set CellRangeRef
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term -> Set CellRangeRef
forall t. Recalc t => t -> Set CellRangeRef
depsOf [Term
x, Term
y]
Ref SheetRef
sheetRef CellAddr
ca -> CellRangeRef -> Set CellRangeRef
forall a. a -> Set a
Set.singleton (SheetRef -> SheetId
sheetId SheetRef
sheetRef, (CellAddr
ca, CellAddr
ca))
Sum SheetRef
sheetRef CellRange
cr -> CellRangeRef -> Set CellRangeRef
forall a. a -> Set a
Set.singleton (SheetRef -> SheetId
sheetId SheetRef
sheetRef, CellRange
cr)
Term
_ -> Set CellRangeRef
forall a. Set a
Set.empty
inferElaborate :: Term -> FetchOf Term ((), Term)
inferElaborate :: Term -> FetchOf Term ((), Term)
inferElaborate =
((), Term) -> Fetch () () ((), Term, Int) ((), Term)
forall a. a -> Fetch () () ((), Term, Int) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (((), Term) -> Fetch () () ((), Term, Int) ((), Term))
-> (Term -> ((), Term))
-> Term
-> Fetch () () ((), Term, Int) ((), Term)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((),) (Term -> ((), Term)) -> (Term -> Term) -> Term -> ((), Term)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
Term
Funky -> Int -> Term
Num Int
42
Term
t -> Term
t
eval :: Term -> FetchOf Term Int
eval :: Term -> FetchOf Term Int
eval = \case
Num Int
n -> Int -> Fetch () () ((), Term, Int) Int
forall a. a -> Fetch () () ((), Term, Int) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
n
Add Term
x Term
y -> Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Int -> Int -> Int)
-> Fetch () () ((), Term, Int) Int
-> Fetch () () ((), Term, Int) (Int -> Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Recalc t => ElaborationOf t -> FetchOf t (ValueOf t)
eval @Term ElaborationOf Term
Term
x Fetch () () ((), Term, Int) (Int -> Int)
-> Fetch () () ((), Term, Int) Int
-> Fetch () () ((), Term, Int) Int
forall a b.
Fetch () () ((), Term, Int) (a -> b)
-> Fetch () () ((), Term, Int) a -> Fetch () () ((), Term, Int) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Recalc t => ElaborationOf t -> FetchOf t (ValueOf t)
eval @Term ElaborationOf Term
Term
y
Ref SheetRef
sheetRef CellAddr
ref -> forall t. CellRef -> FetchOf t (ValueOf t)
fetchValue @Term (SheetRef -> SheetId
sheetId SheetRef
sheetRef, CellAddr
ref)
Sum SheetRef
sheetRef (CellAddr
start, CellAddr
end) ->
[Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
([Int] -> Int)
-> Fetch () () ((), Term, Int) [Int]
-> Fetch () () ((), Term, Int) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Fetch () () ((), Term, Int) Int]
-> Fetch () () ((), Term, Int) [Int]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence
[ forall t. CellRef -> FetchOf t (ValueOf t)
fetchValue @Term (SheetRef -> SheetId
sheetId SheetRef
sheetRef, (Int
i, Int
j))
| Int
i <- [CellAddr -> Int
row CellAddr
start .. CellAddr -> Int
row CellAddr
end]
, Int
j <- [CellAddr -> Int
column CellAddr
start .. CellAddr -> Int
column CellAddr
end]
]
Term
Funky -> () -> Fetch () () ((), Term, Int) Int
forall err env r a. err -> Fetch env err r a
throwSemanticError ()