module Model.CellContent (NamedReference (..),Reference (..) ,CompileReason (..),RuntimeReason (..) ,CellExpr (..),CellValue (..) ,Symbol,dependencies) where import Data.List (intercalate) import CellCoordinate (CellCoord) import I18n (__) type Symbol = String data NamedReference = NamedCell (String,String) | NamedRange ((String,String),(String,String)) | NamedColumn String | NamedRow String deriving (Eq) instance Show NamedReference where show (NamedCell (r,c)) = concat ["$",r,",",c,"$"] show (NamedRange (a,b)) = concat [ show $ NamedCell a , ":",show $ NamedCell b] show (NamedColumn a) = concat ["$_,",a,"$"] show (NamedRow a) = concat ["$",a,"_$"] data Reference = Cell CellCoord | Range (CellCoord,CellCoord) | Column Int | Row Int deriving (Eq,Show) 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 | Inherited CellValue RuntimeReason | UnknownIdentifier Symbol deriving (Eq) instance Show RuntimeReason where show (CompileError a) = unwords [(__ "Compile error") ++ ":",show a] show (TypeError a) = unwords [__ "Type error in",showValueInError a] show (Inherited a b) = unwords [__ "In",showValueInError a,":",show b] 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 | Sub CellExpr | CompileErrorExpr CompileReason deriving (Eq,Show) data CellValue = EmptyValue | NumberValue Double | StringValue String | ListValue [CellValue] | Error RuntimeReason deriving (Eq) instance Show CellValue where show EmptyValue = "" show (NumberValue a) = show a show (StringValue a) = a show (ListValue a) = concat ["[",intercalate "," $ map show a,"]"] show (Error _) = __ "Error" dependencies :: CellExpr -> [Reference] dependencies expr = case expr of Reference ref -> [ref] ListExpr a -> concat $ map dependencies a UnaryOp _ a -> dependencies a BinaryOp _ a b -> (dependencies a) ++ (dependencies b) Call _ a -> dependencies a Sub a -> dependencies a _ -> [] showValueInError :: CellValue -> String showValueInError value = case value of EmptyValue -> __ "Empty" ListValue a -> concat ["[",intercalate "," $ map showValueInError a,"]"] _ -> show value