{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} module Syntax where import Data.List -- ABSTRACT SYNTAX FOR TransformeR -- A transformation has a name, is signed by a record-type -- and a return-data descriptor and has a body -- data Transformation = TRANS Name Sig Sig Body data Transformation = TRANS Name Sig Sig Expression -- deriving Show instance Show Transformation where show (TRANS arg tau1 tau2 e) = concat [ "transform (", arg, " : ", show tau1, ")\n" , " : ", show tau2, "\n" , " {", show e, "}"] -- The body is just a record -- type Body = Rec -- Record-type encodes column names and their descriptors data Sig = Sig [(Name, Descriptor)] instance Show Sig where show (Sig nds) = concat [ "{" , concat . (intersperse ", ") $ map (\(n, d) -> n ++ " : " ++ show d) nds , "}"] -- Severely restricted expressions! -- data Expression = Name Name -- an exp can be a field access -- | OP OPR [Expression] -- or some simple arithmetics -- | LIT Value -- or a literall -- deriving Show data Expression = LIT Value | PROJ Expression Field | OP OPR [Expression] | REC [(Field, Expression)] | VAR Name | MUTATE Name Field Expression | SEQ Expression Expression | ASSIGN Name Expression instance Show Expression where show (LIT v) = show v show (PROJ e f) = concat [show e, "[", f, "]"] -- show (PROJ e f) = "(PROJ " ++ show e ++ show f ++ ")" show (OP opr es) = concat [show opr, "(", (concat . intersperse ", " . map show) es, ")"] show (REC fes) = concat [ "{" , (concat . intersperse ", ") (map (\(f, e) -> f ++ " = " ++ show e) fes) , "}"] show (VAR x) = x show (MUTATE n f e) = concat [n, "[", f, "]:=", show e] show (SEQ e1 e2) = show e1 ++ "; " ++ show e2 show (ASSIGN n e) = n ++ ":=" ++ show e type Field = String type Rec = [(Name, Expression)] -- Descriptor encodes range of data type Descriptor = Range data Range = INTERVAL Number Number | SET [Name] instance Show Range where show (INTERVAL lb ub) = concat ["N[", show lb, ", ", show ub, "]"] show (SET ns) = concat ["C[", concat $ (intersperse ", ") (map show ns), "]"] type Name = String data Value = NUM Number | CAT Category | MAP [(Field, Value)] instance Show Value where show (NUM n) = show n show (CAT c) = show c show (MAP fvs) = concat ["{", (concat . intersperse ", ") (map (\(f, v) -> f ++ " = " ++ show v) fvs), "}"] type Number = Double type Category = String data OPR = SUM | CONCAT instance Show OPR where show SUM = "+" show CONCAT = "*"