I recently came across a list of challenging projects. Most seemed like something I had already done; but the spreadsheet caught my eye. Since I wanted to learn more about Reflex anyway, why not do it in Reflex?
First: the model as a DAG
If you don’t care about the model you can jump right to the next section. Here’s an overview over the API we will build in this section:
data Coord -- the coordinates of a cell
data Expr -- an expression in a cell
parseExpr :: String -> Maybe Expr
data Sheet -- a spreadsheet as a directed acyclic graph
data EvalError = CyclicDependencies [Coord]
emptySheet :: Sheet
update :: Coord -> Expr -> Sheet -> Either EvalError Sheet
lookupCoord :: Coord -> Sheet -> Maybe Int
Lets start by building a language for expressions:
data Coord = Coord String Int
deriving (Eq, Ord)
instance Show Coord where
show (Coord s i) = map toUpper s ++ show i
instance Read Coord where
readPrec = parens $ prec 10 $ do
s <- lift $ munch1 isUpper
n <- lift $ readDecP
pure $ Coord s n
data Expr
= IntVal Int
| Add Expr Expr
| Times Expr Expr
| Dependency Coord
deriving (Eq, Ord)
instance Show Expr where
show (IntVal i) = show i
show (Add e1 e2) = show e1 ++ "+" ++ show e2
show (Times e1 e2) = show e1 ++ "*" ++ show e2
show (Dependency d) = show d
instance Read Expr where
readPrec = parens $
(prec 10 $ IntVal <$> lift readDecP)
+++ (prec 10 $ Dependency <$> readPrec)
+++ (prec 5 $ do
e1 <- step readPrec
Symbol "+" <- lexP
e2 <- readPrec
pure $ Add e1 e2)
+++ (prec 6 $ do
e1 <- step readPrec
Symbol "*" <- lexP
e2 <- readPrec
pure $ Times e1 e2)
parseExpr :: String -> Maybe Expr
parseExpr = go . filter (/=' ')
where
go "" = Just $ IntVal 0
go s = readMaybe s
The Read and Show instances allow us to parse and display expressions. We also accept the empty string, since Nothing stands for a parse failure here and an empty cell should have value 0.
Lets build a model for our spreadsheet next! Since cells may depend on each other we need to build a directed acyclic graph of dependencies.
newtype Sheet = Sheet { unSheet :: Map Coord Cell }
deriving (Eq, Ord, Show)
data Cell = Cell
{ cellDeps :: Set Coord -- ^ cells that this depends on
, cellFounds :: Set Coord -- ^ cells that depend on this
, cellExpr :: Expr
, cellValue :: Int
} deriving (Eq, Ord, Show)
data EvalError
= CyclicDependencies [Coord]
deriving (Eq, Ord, Show)
We can connect this to our expressions:
evaluate :: Expr -> Sheet -> Int
evaluate e (Sheet m) = go e
where
go (IntVal i) = i
go (Dependency d) = case Map.lookup d m of
Nothing -> 0
Just c -> cellValue c
go (Add e1 e2) = go e1 + go e2
go (Times e1 e2) = go e1 * go e2
dependencies :: Expr -> Set Coord
dependencies = go mempty
where
go acc (IntVal _) = acc
go acc (Add e1 e2) = go (go acc e1) e2
go acc (Times e1 e2) = go (go acc e1) e2
go acc (Dependency d) = Set.insert d acc
We will start with an empty map as our sheet and add new cells as they are being written or referenced. We can handle input by calling the update function:
nullCell :: Cell
nullCell = Cell mempty mempty (IntVal 0) 0
addDependency :: Coord -> Coord -> Sheet -> Sheet
addDependency parent child (Sheet m) =
let c = Map.findWithDefault nullCell child m
in Sheet $ Map.insert child
(c { cellFounds = Set.insert parent $ cellFounds c }) m
update :: Coord -> Expr -> Sheet -> Either EvalError Sheet
update p e (Sheet m) = case Map.lookup p m of
Just c -> recompute p $ go (cellFounds c) -- see below for recompute
Nothing -> Right (go mempty)
where
value = evaluate e (Sheet m)
newDeps = dependencies e
newCell founds = Cell newDeps founds e value
go founds = Sheet $ Map.insert p (newCell founds) $ unSheet $
foldl' (\m d -> addDependency p d m) (Sheet m) newDeps
When a cell changed we need to recompute all cells that depend on this cell recursively. If we encounter our original cell in the process we have a cycle and report it. We will assume though that every cycle in our graph must involve p, e.g. that the graph was acyclic before we updated p.
data RecomputeState = RecomputeState
{ currentPath :: [Coord]
, uptodate :: Set Coord
, todos :: Set Coord
, currentSheet :: Sheet
} deriving (Eq, Ord, Show)
-- | Compute all cells that depend on p.
recompute :: Coord -> Sheet -> Either EvalError Sheet
recompute p sheet = fmap (currentSheet . snd) $ runExcept
$ runStateT (mapM_ go (cellFounds pCell))
(RecomputeState [] mempty (cellFounds pCell) sheet)
where
pCell = fromMaybe nullCell $ Map.lookup p $ unSheet sheet
go q = do
s <- get
when (q == p) $
throwError $ CyclicDependencies $ (q:) $ currentPath s
when (q `Set.member` uptodate s) $ pure ()
let nCell = fromMaybe nullCell $ Map.lookup q
$ unSheet $ currentSheet s
mapM_ go $ Set.toList $ Set.intersection (cellDeps nCell) (todos s)
s <- get
let v = evaluate (cellExpr nCell) (currentSheet s)
put $ s
{ todos = (cellFounds nCell) <> Set.delete q (todos s)
, currentPath = q : currentPath s
, currentSheet = Sheet $ Map.insert q (nCell {cellValue = v})
$ unSheet $ currentSheet s
, uptodate = Set.insert q (uptodate s)
}
mapM_ go (cellFounds nCell)
s <- get
put $ s { currentPath = tail $ currentPath s }
Adding a Reflex UI
The most basic component in our spreadsheet is going to be a single cell. It shows the value of the corresponding cell in the spreadsheet when not focused and the corresponding expression when focused. Furthermore we want the cell to have an hasError attribute when an error occurred.
cell :: (DomBuilder t m, MonadFix m, MonadHold t m)
=> Coord -> Dynamic t Bool -> Dynamic t Sheet -> m (Event t Expr)
cell coord errored sheet = mdo
expr <- holdDyn "" $ gate (current $ _inputElement_hasFocus input)
$ _inputElement_input input
let value = (maybe "" (T.pack . show) . lookupCoord coord) <$> sheet
let view = _inputElement_hasFocus input >>= \b ->
if b then expr else value
let cur = (parseExpr . T.unpack) <$> expr
let err = (&&) <$> (not <$> _inputElement_hasFocus input)
<*> ((||) <$> errored <*> (isNothing <$> cur))
input <- inputElement
$ modifyAttributes .~
((\b -> "hasError" =: if b then Just "" else Nothing) <$> updated err)
$ def & inputElementConfig_setValue .~ updated view
pure $ fmapMaybe id $ updated cur
It is remarkable how readable the code is once you get used to it. value
is always the value of the cell in the sheet, expr
is the content of the input
field when it has focus. We set the value of the input field to view
. If the field doesn’t have focus and we either couldn’t parse the expression or get an error signal from outside, the field gets the attribute hasError
.
A grid is just a collection of cells plus some extra state:
grid :: (DomBuilder t m, MonadFix m, MonadHold t m)
=> m (Dynamic t Sheet)
grid = mdo
sheet <- holdDyn emptySheet (fmapMaybe (either (const Nothing) Just)
$ attachWith (flip ($)) (current sheet) changes)
cycle <- holdDyn [] -- a possible cycle in the definitions
$ fmapMaybe (either (\(CyclicDependencies d) -> Just d) (\_ -> Just []))
$ attachWith (flip ($)) (current sheet) changes
el "tr" $ sequence_ $ (el "th" (text "")) :
[ el "th" (text (T.pack (a:[]))) | a <- ['A'..'B']]
cs <- concat <$> sequenceA
[ el "tr" $ sequenceA $ (el "td" (text (T.pack (show n)) >> pure never))
: [ el "td" $ fmap (c, ) <$> cell c ((c `elem`) <$> cycle) sheet
| a <- ['A'..'B'], let c = read (a:(show n))]
| n <- [1..4]]
let changes = mergeWith (\f g s -> f s >>= g)
$ map (fmap (\(p,e) -> update p e)) cs
pure sheet
We pass an error code to the cell if it is part of a cycle. We make sure to arrange the cells in a table with headers.
Finally, we just plug the grid into our site and we are done!
frontend :: Frontend (R FrontendRoute)
frontend = Frontend
{ _frontend_head = do
el "title" $ text "Literally Excel!"
el "style" $ text "input[hasError] { border: 3px solid red; } "
, _frontend_body = do
_ <- grid
return ()
}
Conclusion
I am still unsure, whether I would build a bigger project with Reflex. On the one hand, the cell widget above would have been a lot harder to build in any other language and I am impressed by the ease with which it is possible to pass state around. But there are some pain-points:
- The documentation isn’t that good. When I first looked at
InputElement
I thought that _inputElement_input
referred to the input as typed by the user with one event for every character. Then I thought that _inputElement_input == updated _inputElemen
t_value. Both are wrong and I am still not sure what _inputElement_value
does. - My current solution is unbearably slow on normal-sized spreadsheets (26*100 cells). It seems like reflex is adding all the input elements to the dom and then needs a few seconds to place them at the right location and add the event handlers.
Still, it feels like reflex is getting more usable: Thanks to Obelisk installing it is now a breeze and there are enough tutorials to get started. If you are interested in FRP you should give Reflex a try!