Skip to content

Instantly share code, notes, and snippets.

@queertypes
Created September 30, 2016 21:30
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save queertypes/c61dc3e5808e81ac5e7dfff47899ad3e to your computer and use it in GitHub Desktop.
Save queertypes/c61dc3e5808e81ac5e7dfff47899ad3e to your computer and use it in GitHub Desktop.
A quick mock-up of a spreadsheet program's structure - because why not
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
module Spreadsheet where
import Data.Text
import Data.Word
import Data.Vector
newtype Row = Row Word32
newtype Col = Col Word32
--------------------------------------------------------------------------------
-- Spreadsheet Language --
--------------------------------------------------------------------------------
-- catch some errors at compile-time with GADTs
-- e.g., never mix up bool and numeric ops during eval
-- no text support yet
data Expr a where
-- numeric operators
Add :: Expr Double -> Expr Double -> Expr Double -- expr + expr
Subtract :: Expr Double -> Expr Double -> Expr Double -- expr - expr
Multiply :: Expr Double -> Expr Double -> Expr Double -- expr * expr
Divide :: Expr Double -> Expr Double -> Expr Double -- expr / expr
Power :: Expr Double -> Expr Double -> Expr Double -- expr ^ expr
Sin :: Expr Double -> Expr Double -- sin(expr)
Negate :: Expr Double -> Expr Double -- -expr
Cos :: Expr Double -> Expr Double -- cos(expr)
Tan :: Expr Double -> Expr Double -- tan(expr)
-- array operators
Sum :: [Expr Double] -> Expr Double -- sum (expr, expr, expr, ...)
Any :: [Expr Bool] -> Expr Bool -- any (expr, expr, expr, ...)
All :: [Expr Bool] -> Expr Bool -- all (expr, expr, expr, ...)
Product :: [Expr Double] -> Expr Double -- product (expr, expr, expr, ...)
-- boolean operators
LessThan :: Expr Double-> Expr Double -> Expr Bool -- expr < expr
GreaterThan :: Expr Double-> Expr Double -> Expr Bool -- expr > expr
EqualTo :: Expr Double-> Expr Double -> Expr Bool -- expr == expr
LessThanEqual :: Expr Double-> Expr Double -> Expr Bool -- expr <= expr
GreaterThanEqual :: Expr Double-> Expr Double -> Expr Bool -- expr >= expr
And :: Expr Bool-> Expr Bool -> Expr Bool -- expr & expr
Or :: Expr Bool -> Expr Bool -> Expr Bool -- expr | expr
-- operational ops: affect env
Assign :: Expr a -> Expr a -- = <expr>
Parens :: Expr a -> Expr a -- (expr)
-- Terminal nodes
Number :: Double -> Expr Double -- a number
Reference :: Row -> Col -> Expr a -- $C1
Boolean :: Bool -> Expr Bool -- true | false
--------------------------------------------------------------------------------
-- Spreadsheet State --
--------------------------------------------------------------------------------
data Spreadsheet
= Spreadsheet (Vector Cell) -- 2D structure flattened to 1D
data Cell
= Empty
| forall a. Filled (Expr a) -- lazily evaluated cells
--------------------------------------------------------------------------------
-- Application Model --
-- (Assumes GUI) --
--------------------------------------------------------------------------------
type TextStart = Word32
type TextEnd = Word32
type CursorPos = Word32
type StartRow = Row
type EndRow = Row
type StartCol = Col
type EndCol = Col
type TopLeft = (Row,Col)
type Width = Word32
type Height = Word32
type RegionSize = (Width,Height)
data Region = Region TopLeft RegionSize
data Action
-- valid actions while in a text input box for a cell; edit mode
= Input Char
| DeleteAtPoint Text CursorPos
| BackspaceAtPoint Text CursorPos
| DeleteWordForward Text CursorPos
| DeleteWordBackwards Text CursorPos
| SelectText TextStart TextEnd
| SelectAll
| CopyText TextStart TextEnd
| CutText TextStart TextEnd
| Paste Text CursorPos
| FinalizeEdit
-- valid actions while on a cell; sheet mode
-- leaving off paste functionality for now
| StartEdit Row Col
| ClearCell Row Col
| CopyCell Row Col
| SelectColumn Col
| SelectRow Row
| SelectRegion Region
| ClearCells Region
| CopyCells Region
-- movement over cells; sheet mode
| MoveRight
| MoveLeft
| MoveUp
| MoveDown
-- auxiliary operations; sheet mode
| Quit
| LoadFrom FilePath
| SaveCurrent
| SaveTo FilePath
--------------------------------------------------------------------------------
-- Parser --
--------------------------------------------------------------------------------
data ParseError
parseExpr :: String -> Either ParseError (Expr a)
parseExpr = undefined
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment