{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Ivory.Language.Syntax.AST where
import Prelude ()
import Prelude.Compat
import Ivory.Language.Syntax.Concrete.Location
import Ivory.Language.Syntax.Names
import Ivory.Language.Syntax.Type
import Language.Haskell.TH.Lift (deriveLiftMany)
#if __GLASGOW_HASKELL__ < 709
import Language.Haskell.TH.Syntax (Lift (..))
#endif
import Data.Ratio (denominator,
numerator)
import Data.Semigroup (Semigroup(..))
type ModulePath = String
data Visible a = Visible
{ public :: [a]
, private :: [a]
} deriving (Show, Eq, Ord)
instance Semigroup (Visible a) where
Visible l0 l1 <> Visible m0 m1 = Visible (l0 ++ m0) (l1 ++ m1)
instance Monoid (Visible a) where
mempty = Visible [] []
mappend = (<>)
type ModuleName = String
data Module = Module
{ modName :: ModuleName
, modHeaders :: [FilePath]
, modDepends :: [ModuleName]
, modExterns :: [Extern]
, modImports :: [Import]
, modProcs :: Visible Proc
, modStructs :: Visible Struct
, modAreas :: Visible Area
, modAreaImports :: [AreaImport]
} deriving (Show, Eq, Ord)
instance Semigroup Module where
l <> r = Module
{ modName = modName (if null (modName l) then r else l)
, modHeaders = modHeaders l <> modHeaders r
, modDepends = modDepends l <> modDepends r
, modExterns = modExterns l <> modExterns r
, modImports = modImports l <> modImports r
, modProcs = modProcs l <> modProcs r
, modStructs = modStructs l <> modStructs r
, modAreas = modAreas l <> modAreas r
, modAreaImports = modAreaImports l <> modAreaImports r
}
instance Monoid Module where
mempty = Module
{ modName = ""
, modHeaders = []
, modDepends = []
, modExterns = []
, modImports = []
, modProcs = mempty
, modStructs = mempty
, modAreas = mempty
, modAreaImports = []
}
mappend = (<>)
data Import = Import
{ importSym :: Sym
, importFile :: ModulePath
, importRetTy :: Type
, importArgs :: [Typed Var]
, importRequires :: [Require]
, importEnsures :: [Ensure]
} deriving (Show, Eq, Ord)
data Proc = Proc
{ procSym :: Sym
, procRetTy :: Type
, procArgs :: [Typed Var]
, procBody :: Block
, procRequires :: [Require]
, procEnsures :: [Ensure]
} deriving (Show, Eq, Ord)
data Struct
= Struct String [Typed String]
| Abstract String ModulePath
deriving (Show, Eq, Ord)
structName :: Struct -> String
structName def = case def of
Struct n _ -> n
Abstract n _ -> n
data Area = Area
{ areaSym :: Sym
, areaConst :: Bool
, areaType :: Type
, areaInit :: Init
} deriving (Show, Eq, Ord)
data AreaImport = AreaImport
{ aiSym :: Sym
, aiConst :: Bool
, aiFile :: ModulePath
} deriving (Show, Eq, Ord)
type Block = [Stmt]
data Stmt
= IfTE Expr Block Block
| Assert Expr
| CompilerAssert Expr
| Assume Expr
| Return (Typed Expr)
| ReturnVoid
| Deref Type Var Expr
| Store Type Expr Expr
| Assign Type Var Expr
| Call Type (Maybe Var) Name [Typed Expr]
| Local Type Var Init
| RefCopy Type Expr Expr
| RefZero Type Expr
| AllocRef Type Var Name
| Loop Integer Var Expr LoopIncr Block
| Forever Block
| Break
| Comment Comment
deriving (Show, Eq, Ord)
data LoopIncr
= IncrTo Expr
| DecrTo Expr
deriving (Show, Eq, Ord)
data Name
= NameSym Sym
| NameVar Var
deriving (Show, Eq, Ord)
data Comment = UserComment String
| SourcePos SrcLoc
deriving (Show, Eq, Ord)
data Cond
= CondBool Expr
| CondDeref Type Expr Var Cond
deriving (Show, Eq, Ord)
newtype Require = Require
{ getRequire :: Cond
} deriving (Show, Eq, Ord)
newtype Ensure = Ensure
{ getEnsure :: Cond
} deriving (Show, Eq, Ord)
data Extern = Extern
{ externSym :: Sym
, externFile :: ModulePath
, externType :: Type
} deriving (Show, Eq, Ord)
data Expr
= ExpSym Sym
| ExpExtern Extern
| ExpVar Var
| ExpLit Literal
| ExpLabel Type Expr String
| ExpIndex Type Expr Type Expr
| ExpToIx Expr Integer
| ExpSafeCast Type Expr
| ExpOp ExpOp [Expr]
| ExpAddrOfGlobal Sym
| ExpMaxMin Bool
| ExpSizeOf Type
deriving (Show, Eq, Ord)
data ExpOp
= ExpEq Type
| ExpNeq Type
| ExpCond
| ExpGt Bool Type
| ExpLt Bool Type
| ExpNot
| ExpAnd
| ExpOr
| ExpMul
| ExpAdd
| ExpSub
| ExpNegate
| ExpAbs
| ExpSignum
| ExpDiv
| ExpMod
| ExpRecip
| ExpFExp
| ExpFSqrt
| ExpFLog
| ExpFPow
| ExpFLogBase
| ExpFSin
| ExpFTan
| ExpFCos
| ExpFAsin
| ExpFAtan
| ExpFAtan2
| ExpFAcos
| ExpFSinh
| ExpFTanh
| ExpFCosh
| ExpFAsinh
| ExpFAtanh
| ExpFAcosh
| ExpIsNan Type
| ExpIsInf Type
| ExpRoundF
| ExpCeilF
| ExpFloorF
| ExpBitAnd
| ExpBitOr
| ExpBitXor
| ExpBitComplement
| ExpBitShiftL
| ExpBitShiftR
deriving (Show, Eq, Ord)
instance Num Expr where
l * r = ExpOp ExpMul [l,r]
l + r = ExpOp ExpAdd [l,r]
l - r = ExpOp ExpSub [l,r]
abs e = ExpOp ExpAbs [e]
signum e = ExpOp ExpSignum [e]
negate (ExpLit (LitInteger i)) = ExpLit (LitInteger (negate i))
negate (ExpLit (LitFloat f)) = ExpLit (LitFloat (negate f))
negate (ExpLit (LitDouble d)) = ExpLit (LitDouble (negate d))
negate e = ExpOp ExpNegate [e]
fromInteger i = ExpLit (LitInteger i)
instance Bounded Expr where
minBound = ExpMaxMin False
maxBound = ExpMaxMin True
instance Fractional Expr where
l / r = ExpOp ExpDiv [l,r]
recip a = ExpOp ExpRecip [a]
fromRational a = fromInteger (numerator a) / fromInteger (denominator a)
instance Floating Expr where
pi = error "pi not implemented for Expr"
exp e = ExpOp ExpFExp [e]
sqrt e = ExpOp ExpFSqrt [e]
log e = ExpOp ExpFLog [e]
a ** b = ExpOp ExpFPow [a,b]
logBase a b = ExpOp ExpFLogBase [a,b]
sin e = ExpOp ExpFSin [e]
tan e = ExpOp ExpFTan [e]
cos e = ExpOp ExpFCos [e]
asin e = ExpOp ExpFAsin [e]
atan e = ExpOp ExpFAtan [e]
acos e = ExpOp ExpFAcos [e]
sinh e = ExpOp ExpFSinh [e]
tanh e = ExpOp ExpFTanh [e]
cosh e = ExpOp ExpFCosh [e]
asinh e = ExpOp ExpFAsinh [e]
atanh e = ExpOp ExpFAtanh [e]
acosh e = ExpOp ExpFAcosh [e]
data Literal
= LitInteger Integer
| LitFloat Float
| LitDouble Double
| LitChar Char
| LitBool Bool
| LitNull
| LitString String
deriving (Show, Eq, Ord)
zeroInit :: Init
zeroInit = InitZero
data Init
= InitZero
| InitExpr Type Expr
| InitStruct [(String,Init)]
| InitArray [Init] Bool
deriving (Show, Eq, Ord)
deriveLiftMany
[ ''Module, ''Visible, ''AreaImport, ''Area, ''Struct
, ''Import
, ''Extern
, ''Proc, ''Ensure, ''Require, ''Cond
, ''Name
, ''Stmt, ''LoopIncr, ''Comment, ''SrcLoc, ''Range, ''Position
, ''Expr, ''ExpOp, ''Literal, ''Init
]
#if __GLASGOW_HASKELL__ < 709
instance Lift Double where
lift = lift . toRational
instance Lift Float where
lift = lift . toRational
#endif