disco-0.1.3.1: Functional programming language for teaching discrete math.
Copyrightdisco team and contributors
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellNone
LanguageHaskell2010

Disco.AST.Typed

Description

Typed abstract syntax trees representing the typechecked surface syntax of the Disco language. Each tree node is annotated with the type of its subtree.

Synopsis

Type-annotated terms

type ATerm = Term_ TY Source #

An ATerm is a typechecked term where every node in the tree has been annotated with the type of the subterm rooted at that node.

pattern ATVar :: Type -> QName ATerm -> ATerm Source #

pattern ATPrim :: Type -> Prim -> ATerm Source #

pattern ATUnit :: ATerm Source #

pattern ATBool :: Type -> Bool -> ATerm Source #

pattern ATNat :: Type -> Integer -> ATerm Source #

pattern ATRat :: Rational -> ATerm Source #

pattern ATChar :: Char -> ATerm Source #

pattern ATString :: String -> ATerm Source #

pattern ATApp :: Type -> ATerm -> ATerm -> ATerm Source #

pattern ATTup :: Type -> [ATerm] -> ATerm Source #

pattern ATCase :: Type -> [ABranch] -> ATerm Source #

pattern ATChain :: Type -> ATerm -> [ALink] -> ATerm Source #

pattern ATTyOp :: Type -> TyOp -> Type -> ATerm Source #

pattern ATList :: Type -> [ATerm] -> Maybe (Ellipsis ATerm) -> ATerm Source #

pattern ATTest :: [(String, Type, Name ATerm)] -> ATerm -> ATerm Source #

type ALink = Link_ TY Source #

pattern ATLink :: BOp -> ATerm -> ALink Source #

data Container where Source #

An enumeration of the different kinds of containers in disco: lists, bags, and sets.

Instances

Instances details
Enum Container Source # 
Instance details

Defined in Disco.AST.Generic

Eq Container Source # 
Instance details

Defined in Disco.AST.Generic

Data Container Source # 
Instance details

Defined in Disco.AST.Generic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Container -> c Container #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Container #

toConstr :: Container -> Constr #

dataTypeOf :: Container -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Container) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Container) #

gmapT :: (forall b. Data b => b -> b) -> Container -> Container #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Container -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Container -> r #

gmapQ :: (forall d. Data d => d -> u) -> Container -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Container -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Container -> m Container #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Container -> m Container #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Container -> m Container #

Show Container Source # 
Instance details

Defined in Disco.AST.Generic

Generic Container Source # 
Instance details

Defined in Disco.AST.Generic

Associated Types

type Rep Container :: Type -> Type #

Alpha Container Source # 
Instance details

Defined in Disco.AST.Generic

Subst t Container Source # 
Instance details

Defined in Disco.AST.Generic

type Rep Container Source # 
Instance details

Defined in Disco.AST.Generic

type Rep Container = D1 ('MetaData "Container" "Disco.AST.Generic" "disco-0.1.3.1-EVUeP3Z0O0d8zqKlGvDqh1" 'False) (C1 ('MetaCons "ListContainer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BagContainer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetContainer" 'PrefixI 'False) (U1 :: Type -> Type)))

Branches and guards

type AGuard = Guard_ TY Source #

pattern AGLet :: ABinding -> AGuard Source #

type AQual = Qual_ TY Source #

pattern APVar :: Type -> Name ATerm -> APattern Source #

pattern APWild :: Type -> APattern Source #

pattern APUnit :: APattern Source #

pattern APBool :: Bool -> APattern Source #

pattern APTup :: Type -> [APattern] -> APattern Source #

pattern APInj :: Type -> Side -> APattern -> APattern Source #

pattern APNat :: Type -> Integer -> APattern Source #

pattern APChar :: Char -> APattern Source #

pattern APList :: Type -> [APattern] -> APattern Source #

pattern APAdd :: Type -> Side -> APattern -> ATerm -> APattern Source #

pattern APMul :: Type -> Side -> APattern -> ATerm -> APattern Source #

pattern APSub :: Type -> APattern -> ATerm -> APattern Source #

pattern APNeg :: Type -> APattern -> APattern Source #

Utilities

getType :: HasType t => t -> Type Source #

Get the type of a thing.

setType :: HasType t => Type -> t -> t Source #

Set the type of a thing, when that is possible; the default implementation is for setType to do nothing.