module Curry.FlatCurry.Annotated.Type
( module Curry.FlatCurry.Annotated.Type
, module Curry.FlatCurry.Typeable
, module Curry.FlatCurry.Type
) where
import Curry.FlatCurry.Typeable
import Curry.FlatCurry.Type ( QName, VarIndex, Visibility (..), TVarIndex
, TypeDecl (..), OpDecl (..), Fixity (..)
, TypeExpr (..), ConsDecl (..)
, Literal (..), CombType (..), CaseType (..)
)
data AProg a = AProg String [String] [TypeDecl] [AFuncDecl a] [OpDecl]
deriving (Eq, Read, Show)
data AFuncDecl a = AFunc QName Int Visibility TypeExpr (ARule a)
deriving (Eq, Read, Show)
data ARule a
= ARule a [(VarIndex, a)] (AExpr a)
| AExternal a String
deriving (Eq, Read, Show)
data AExpr a
= AVar a VarIndex
| ALit a Literal
| AComb a CombType (QName, a) [AExpr a]
| ALet a [((VarIndex, a), AExpr a)] (AExpr a)
| AFree a [(VarIndex, a)] (AExpr a)
| AOr a (AExpr a) (AExpr a)
| ACase a CaseType (AExpr a) [ABranchExpr a]
| ATyped a (AExpr a) TypeExpr
deriving (Eq, Read, Show)
data ABranchExpr a = ABranch (APattern a) (AExpr a)
deriving (Eq, Read, Show)
data APattern a
= APattern a (QName, a) [(VarIndex, a)]
| ALPattern a Literal
deriving (Eq, Read, Show)
instance Typeable a => Typeable (AExpr a) where
typeOf (AVar a _) = typeOf a
typeOf (ALit a _) = typeOf a
typeOf (AComb a _ _ _) = typeOf a
typeOf (ALet a _ _) = typeOf a
typeOf (AFree a _ _) = typeOf a
typeOf (AOr a _ _) = typeOf a
typeOf (ACase a _ _ _) = typeOf a
typeOf (ATyped a _ _) = typeOf a
instance Typeable a => Typeable (APattern a) where
typeOf (APattern a _ _) = typeOf a
typeOf (ALPattern a _) = typeOf a