module Model.CellContent (CellReference (..),NamedReference (..) ,Reference (..) ,CompileReason (..),RuntimeReason (..) ,CellExpr (..),CellValue (..) ,Symbol,dependencies,showValueInGrid ,valueToExpr) where import Data.List (intercalate) import CellCoordinate (CellCoord) import I18n (__) type Symbol = String data CellReference = Named (String,String) | SameRow String | SameColumn String deriving (Eq) instance Show CellReference where show (Named (r,c)) = concat ["$",r,",",c,"$"] show (SameRow c) = concat ["$=,",c,"$"] show (SameColumn r) = concat ["$",r,",=$"] data NamedReference = NamedCell CellReference | NamedRange (CellReference,CellReference) | NamedColumn String | NamedRow String deriving (Eq) instance Show NamedReference where show (NamedCell ref) = show ref show (NamedRange (a,b)) = concat [show a, ":",show b] show (NamedColumn a) = concat ["$_,",a,"$"] show (NamedRow a) = concat ["$",a,"_$"] data Reference = Cell CellCoord | Range (CellCoord,CellCoord) | Column Int | Row Int deriving (Eq) data CompileReason = ParseError String | RefConversionError NamedReference | ReferenceLoop deriving (Eq) instance Show CompileReason where show (ParseError a) = unwords [(__ "Parse error")++ ":",a] show (RefConversionError a) = unwords [(__ "Unknown reference") ++ ":",show a] show ReferenceLoop = __ "Reference loop" data RuntimeReason = CompileError CompileReason | TypeError CellValue | UnknownIdentifier Symbol deriving (Eq) instance Show RuntimeReason where show (CompileError a) = unwords [(__ "Compile error") ++ ":",show a] show (TypeError (Error a)) = show a show (TypeError a) = unwords [__ "Type error in",show a] show (UnknownIdentifier a) = unwords [__ "Unknown identifier",a] data CellExpr = EmptyExpr | NumberExpr Double | StringExpr String | ListExpr [CellExpr] | NamedReference NamedReference | Reference Reference | UnaryOp Symbol CellExpr | BinaryOp Symbol CellExpr CellExpr | Call Symbol CellExpr | Constant Symbol | Sub CellExpr | IfThenElse CellExpr CellExpr CellExpr | CompileErrorExpr CompileReason deriving (Eq) instance Show CellExpr where show EmptyExpr = "" show (NumberExpr a) = show a show (StringExpr a) = show a show (ListExpr a) = concat ["[",intercalate "," $ map show a,"]"] show (NamedReference a) = show a show (UnaryOp a b) = a ++ show b show (BinaryOp a b c) = unwords [show b,a,show c] show (Call a b) = unwords [a,show b] show (Constant a) = a show (Sub a) = concat ["(",show a,")"] show (IfThenElse a b c) = unwords ["if",show a,"then",show b,"else",show c] data CellValue = EmptyValue | NumberValue Double | StringValue String | ListValue [CellValue] | BoolValue Bool | Error RuntimeReason deriving (Eq) instance Ord CellValue where compare EmptyValue EmptyValue = EQ compare (NumberValue a) (NumberValue b) = compare a b compare (StringValue a) (StringValue b) = compare a b compare (BoolValue a) (BoolValue b) = compare a b instance Show CellValue where show EmptyValue = __ "Empty" show (NumberValue a) = show a show (StringValue a) = a show (ListValue a) = concat ["[",intercalate "," $ map show a,"]"] show (BoolValue True) = "true" show (BoolValue False) = "false" show (Error e) = show e -- -> Model.Grid.referenceConversion dependencies :: CellExpr -> [Reference] dependencies expr = case expr of Reference ref -> [ref] ListExpr a -> concat $ map dependencies a UnaryOp _ a -> dependencies a BinaryOp _ a b -> concatMap dependencies [a,b] Call _ a -> dependencies a Sub a -> dependencies a IfThenElse a b c -> concatMap dependencies [a,b,c] _ -> [] {- replaceBy :: CellExpr -> CellExpr -> CellExpr replaceBy new expr = if expr == new then new else case expr of ListExpr a -> ListExpr $ map (replaceBy new) a UnaryOp a b -> UnaryOp a $ replaceBy new b BinaryOp a b c -> BinaryOp a (replaceBy new b) (replaceBy new c) Call a b -> Call a $ replaceBy new b Sub a -> Sub $ replaceBy new a IfThenElse a b c -> IfThenElse (replaceBy new a) (replaceBy new b) (replaceBy new c) _ -> expr -} valueToExpr :: CellValue -> CellExpr valueToExpr value = case value of EmptyValue -> EmptyExpr NumberValue a -> NumberExpr a StringValue a -> StringExpr a ListValue a -> ListExpr $ map valueToExpr a BoolValue True -> Constant "true" BoolValue False -> Constant "false" showValueInGrid :: CellValue -> String showValueInGrid value = case value of EmptyValue -> "" ListValue a -> concat ["[",intercalate "," $ map showValueInGrid a,"]"] Error _ -> __ "Error" _ -> show value