recalc-engine
Safe HaskellSafe-Inferred
LanguageGHC2021

Recalc.Engine

Description

The evaluation strategy is inspired by the paper "Build systems à la carte", it maintains a DocumentStore that tracks types, values and meta data (dummied out for now) for all cells, and a dependency graph of the cells for checking which cells are dirty (need to be recalculated).

References: Andrey Mokhov, Neil Mitchell and Simon Peyton Jones. Build Systems à la Carte. Proceedings of the ACM on Programming Languages, Volume 2, Issue ICFP.

Synopsis

Engine Operations

type Inputs = [(CellRef, (Maybe (String, CellType), Meta))] Source #

inputs are given by the location, maybe an input (and its type), and meta data

type CycleOf t = [(CellRef, CellOf t)] Source #

when there is a dependency cycle, the cycle's locations are returned together with the data stored there

type ResultsOf t = [(CellRef, CellOf t)] Source #

the results are locations and the data stored there

recalc :: forall f. (Recalc f, Show (ErrorOf f)) => Inputs -> EngineStateOf f -> (Either (CycleOf f) (ResultsOf f), EngineStateOf f) Source #

recalculate the inputs and everything that depends on those (transitively), or return the cycle if there is a dependency cycle.

recalcAll :: forall t. (Recalc t, Show (ErrorOf t)) => EngineStateOf t -> (Either (CycleOf t) (ResultsOf t), EngineStateOf t) Source #

recalculate the whole sheet (marking everything as dirty), or return the cycle if there is a dependency cycle.

parseTerm :: Recalc t => CellRef -> (String, CellType) -> Parsed t Source #

parse a cell (depends on the cell's location) returns formula or value (both as term)

Spreadsheet Language Interface

class (Pretty t, Pretty (TypeOf t), Pretty (ElaborationOf t), Pretty (ValueOf t)) => Recalc t where Source #

The spreadsheet language interface. An instantiation of it can be used to declare the semantics of the provided language in a spreadsheet environment.

Minimal complete definition

(infer | inferElaborate), parseCell, depsOf, eval

Associated Types

type EnvOf t Source #

a custom environment (e.g. to bind global variables)

type ErrorOf t Source #

a custom error type (errors during type inference, or evaluation)

type ElaborationOf t Source #

the value t evaluates to

type ElaborationOf t = t

type TypeOf t Source #

the types of values t

type ValueOf t Source #

the value t evaluates to

Methods

parseCell :: CellType -> ReaderT SheetId (Parsec Void String) t Source #

the language may differentiate between cells parsed as formula and value

depsOf :: t -> Set CellRangeRef Source #

specify how to calculate the cell references a term depends on

infer :: t -> FetchOf t (TypeOf t) Source #

specify how a term's type is inferred

inferElaborate :: t -> FetchOf t (TypeOf t, ElaborationOf t) Source #

specify how a term's type is inferred with term elaboration (defaults to identity elaboration)

eval :: ElaborationOf t -> FetchOf t (ValueOf t) Source #

specify how a term is evaluated

Fetch Monad

data Fetch env err r a Source #

Fetch callbacks can fail (using MonadError) and have access to other cells (see fetchType, fetchValue), and the custom context (using MonadReader)

Instances

Instances details
MonadReader env (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

ask :: Fetch env err r env #

local :: (env -> env) -> Fetch env err r a -> Fetch env err r a #

reader :: (env -> a) -> Fetch env err r a #

MonadError (FetchError err) (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

throwError :: FetchError err -> Fetch env err r a #

catchError :: Fetch env err r a -> (FetchError err -> Fetch env err r a) -> Fetch env err r a #

Applicative (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

pure :: a -> Fetch env err r a #

(<*>) :: Fetch env err r (a -> b) -> Fetch env err r a -> Fetch env err r b #

liftA2 :: (a -> b -> c) -> Fetch env err r a -> Fetch env err r b -> Fetch env err r c #

(*>) :: Fetch env err r a -> Fetch env err r b -> Fetch env err r b #

(<*) :: Fetch env err r a -> Fetch env err r b -> Fetch env err r a #

Functor (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

fmap :: (a -> b) -> Fetch env err r a -> Fetch env err r b #

(<$) :: a -> Fetch env err r b -> Fetch env err r a #

Monad (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

(>>=) :: Fetch env err r a -> (a -> Fetch env err r b) -> Fetch env err r b #

(>>) :: Fetch env err r a -> Fetch env err r b -> Fetch env err r b #

return :: a -> Fetch env err r a #

data FetchError err Source #

Evaluation of cells can always fail due to invalid formulas or refs

Constructors

InvalidFormula ParseError 
RefError 
SemanticError err 

Instances

Instances details
Show err => Show (FetchError err) Source # 
Instance details

Defined in Recalc.Engine

Methods

showsPrec :: Int -> FetchError err -> ShowS #

show :: FetchError err -> String #

showList :: [FetchError err] -> ShowS #

Eq err => Eq (FetchError err) Source # 
Instance details

Defined in Recalc.Engine

Methods

(==) :: FetchError err -> FetchError err -> Bool #

(/=) :: FetchError err -> FetchError err -> Bool #

MonadError (FetchError err) (Fetch env err r) Source # 
Instance details

Defined in Recalc.Engine

Methods

throwError :: FetchError err -> Fetch env err r a #

catchError :: Fetch env err r a -> (FetchError err -> Fetch env err r a) -> Fetch env err r a #

Actions

fetchType :: CellRef -> FetchOf t (TypeOf t) Source #

fetch the type of the value at a cell reference

fetchValue :: CellRef -> FetchOf t (ValueOf t) Source #

fetch the value stored at a cell reference

throwSemanticError :: err -> Fetch env err r a Source #

throw user-defined error

Run Action (for debugging purposes)

runFetchWith Source #

Arguments

:: env 
-> (CellRef -> Except (FetchError err) v)

callback that returns a value/type (depending on its kind)

-> Fetch env err v a

a fetch task to run

-> Either (FetchError err) a 

Engine State

type EngineStateOf f = EngineState (EnvOf f) (ErrorOf f) f (TypeOf f) (ElaborationOf f) (ValueOf f) Source #

newEngineState :: env -> EngineState env err f t e v Source #

create a new engine state. the engine state is completely empty, no handles on any documents.

engineEnv :: EngineState env err f t e v -> env Source #

engineDocs :: EngineState env err f t e v -> DocumentStore err f t e v Source #

State Updates

mapEnv :: (env -> env) -> EngineState env err f t e v -> EngineState env err f t e v Source #

modify the custom environment

mapDocs :: (DocumentStore err f t e v -> DocumentStore err f t e v) -> EngineState env err f t e v -> EngineState env err f t e v Source #

modify the document store

deleteSheetId :: SheetId -> EngineState env err f t e v -> EngineState env err f t e v Source #

delete a whole sheet by its id from the dependency graph (useful when renaming a sheet)

Types

type DocumentStoreOf f = DocumentStore (ErrorOf f) f (TypeOf f) (ElaborationOf f) (ValueOf f) Source #

data Document err f t e v Source #

Constructors

Document 

Fields

Instances

Instances details
(Show err, Pretty f, Pretty t, Pretty e, Pretty v) => Show (Document err f t e v) Source # 
Instance details

Defined in Recalc.Engine

Methods

showsPrec :: Int -> Document err f t e v -> ShowS #

show :: Document err f t e v -> String #

showList :: [Document err f t e v] -> ShowS #

type SheetOf f = Sheet (ErrorOf f) f (TypeOf f) (ElaborationOf f) (ValueOf f) Source #

data Cell err f t e v Source #

Constructors

Cell 

Fields

  • cell :: !(Maybe ((String, CellType), Maybe (f, Maybe ((t, e), Maybe v))))

    a cell maybe only meta data. when it has a term (and therefore the input and celltype are available), it can have a type. if it has a type it must have an associated elaborated term, and it can have a value.

  • cellDeps :: !(Set CellRangeRef)

    dependencies of the cell

  • cellError :: !(Maybe (FetchError err))

    when the cell encounters an error (during inference or evaluation)

  • cellMeta :: !Meta

    meta data (currently useless, should include style info like it once did)

Instances

Instances details
(Show err, Pretty f, Pretty t, Pretty e, Pretty v) => Show (Cell err f t e v) Source # 
Instance details

Defined in Recalc.Engine

Methods

showsPrec :: Int -> Cell err f t e v -> ShowS #

show :: Cell err f t e v -> String #

showList :: [Cell err f t e v] -> ShowS #

type CellOf f = Cell (ErrorOf f) f (TypeOf f) (ElaborationOf f) (ValueOf f) Source #

data CellType Source #

Constructors

CellFormula

cell formulas (starting with =)

CellValue

regular values

Instances

Instances details
Show CellType Source # 
Instance details

Defined in Recalc.Engine

data Meta Source #

Constructors

Meta 

Instances

Instances details
Show Meta Source # 
Instance details

Defined in Recalc.Engine

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

re-export core definitions

type CellAddr = (Int, Int) Source #

row and column

readExcel :: Text -> Maybe CellAddr Source #

read an spreadsheet address of the form column-row (columns are labelled "A..Z, AA..", and rows enumerated)

>>> readExcel "A2"
Just (1,0)

showExcel26 :: CellAddr -> String Source #

show a zero-indexed cell address in Excel-style

>>> showExcel (0,4)
"E1"