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

Disco.AST.Surface

Description

Abstract syntax trees representing the surface syntax of the Disco language.

Synopsis

Modules

data Module Source #

A module contains all the information from one disco source file.

Constructors

Module 

Fields

Instances

Instances details
ForallTerm Show UD => Show Module Source # 
Instance details

Defined in Disco.AST.Surface

data TopLevel Source #

A TopLevel is either documentation (a DocThing) or a declaration (Decl).

Instances

Instances details
ForallTerm Show UD => Show TopLevel Source # 
Instance details

Defined in Disco.AST.Surface

Documentation

type Docs = [DocThing] Source #

Convenient synonym for a list of DocThings.

data DocThing Source #

An item of documentation.

Constructors

DocString [String]

A documentation string, i.e. a block of ||| text items

DocProperty Property

An exampledoctestproperty of the form !!! forall (x1:ty1) ... . property

Instances

Instances details
ForallTerm Show UD => Show DocThing Source # 
Instance details

Defined in Disco.AST.Surface

type Property = Property_ UD Source #

A property is a universally quantified term of the form forall v1 : T1, v2 : T2. term.

Declarations

data TypeDecl Source #

A type declaration, name : type.

Constructors

TypeDecl (Name Term) PolyType 

Instances

Instances details
ForallTerm Show UD => Show TypeDecl Source # 
Instance details

Defined in Disco.AST.Surface

data TermDefn Source #

A group of definition clauses of the form name pat1 .. patn = term. The patterns bind variables in the term. For example, f n (x,y) = n*x + y.

Constructors

TermDefn (Name Term) [Bind [Pattern] Term] 

Instances

Instances details
ForallTerm Show UD => Show TermDefn Source # 
Instance details

Defined in Disco.AST.Surface

data TypeDefn Source #

A user-defined type (potentially recursive).

@type T arg1 arg2 ... = body

Constructors

TypeDefn String [String] Type 

Instances

Instances details
Show TypeDefn Source # 
Instance details

Defined in Disco.AST.Surface

data Decl where Source #

A declaration is either a type declaration, a term definition, or a type definition.

Constructors

DType :: TypeDecl -> Decl 
DDefn :: TermDefn -> Decl 
DTyDef :: TypeDefn -> Decl 

Instances

Instances details
ForallTerm Show UD => Show Decl Source # 
Instance details

Defined in Disco.AST.Surface

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Pretty Decl Source # 
Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Decl -> Sem r Doc Source #

prettyTyDecl :: Members '[Reader PA, LFresh] r => Name t -> Type -> Sem r Doc Source #

Pretty-print a type declaration.

Terms

data UD Source #

The extension descriptor for Surface specific AST types.

Instances

Instances details
Pretty Pattern Source # 
Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Pattern -> Sem r Doc Source #

Pretty Guard Source # 
Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Guard -> Sem r Doc Source #

Pretty Branch Source #

Pretty-print a single branch in a case expression.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Branch -> Sem r Doc Source #

Pretty Binding Source #

Pretty-print a binding, i.e. a pairing of a name (with optional type annotation) and term.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Binding -> Sem r Doc Source #

Pretty Qual Source #

Pretty-print a single qualifier in a comprehension.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Qual -> Sem r Doc Source #

Pretty Term Source # 
Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Term -> Sem r Doc Source #

Pretty (Telescope Guard) Source #

Pretty-print the guards in a single branch of a case expression.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Telescope Guard -> Sem r Doc Source #

Pretty (Telescope Qual) Source #

Pretty-print the qualifiers in a comprehension.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Telescope Qual -> Sem r Doc Source #

Pretty (Name a, Bind [Pattern] Term) Source #

Pretty-print a single clause in a definition.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => (Name a, Bind [Pattern] Term) -> Sem r Doc Source #

type X_Binder UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_Pattern UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PFrac UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PFrac UD = ()
type X_PNeg UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PNeg UD = ()
type X_PSub UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PSub UD = ()
type X_PMul UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PMul UD = ()
type X_PAdd UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PAdd UD = ()
type X_PList UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PList UD = ()
type X_PCons UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PCons UD = ()
type X_PString UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PString UD = ()
type X_PChar UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PChar UD = ()
type X_PNat UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PNat UD = ()
type X_PInj UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PInj UD = ()
type X_PTup UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PTup UD = ()
type X_PBool UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PBool UD = ()
type X_PUnit UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PUnit UD = ()
type X_PAscr UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PAscr UD = ()
type X_PWild UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PWild UD = ()
type X_PVar UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_PVar UD = ()
type X_GLet UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_GLet UD = ()
type X_GPat UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_GPat UD = ()
type X_GBool UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_GBool UD = ()
type X_QGuard UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_QGuard UD = ()
type X_QBind UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_QBind UD = ()
type X_TLink UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TLink UD = ()
type X_Term UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_Term UD = ()
type X_TAscr UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TAscr UD = ()
type X_TContainerComp UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TContainer UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TContainer UD = ()
type X_TTyOp UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TTyOp UD = ()
type X_TChain UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TChain UD = ()
type X_TCase UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TCase UD = ()
type X_TTup UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TTup UD = ()
type X_TApp UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TApp UD = ()
type X_TAbs UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TAbs UD = ()
type X_TString UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TString UD = ()
type X_TChar UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TChar UD = ()
type X_TRat UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TRat UD = ()
type X_TNat UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TNat UD = ()
type X_TBool UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TBool UD = ()
type X_TUnit UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TUnit UD = ()
type X_TParens UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TParens UD = ()
type X_TLet UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TLet UD = ()
type X_TPrim UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TPrim UD = ()
type X_TVar UD Source # 
Instance details

Defined in Disco.AST.Surface

type X_TVar UD = ()

pattern TVar :: Name Term -> Term Source #

pattern TPrim :: Prim -> Term Source #

pattern TUn :: UOp -> Term -> Term Source #

pattern TBin :: BOp -> Term -> Term -> Term Source #

pattern TParens :: Term -> Term Source #

pattern TUnit :: Term Source #

pattern TBool :: Bool -> Term Source #

pattern TChar :: Char -> Term Source #

pattern TString :: String -> Term Source #

pattern TNat :: Integer -> Term Source #

pattern TRat :: Rational -> Term Source #

pattern TApp :: Term -> Term -> Term Source #

pattern TTup :: [Term] -> Term Source #

pattern TCase :: [Branch] -> Term Source #

pattern TChain :: Term -> [Link] -> Term Source #

pattern TTyOp :: TyOp -> Type -> Term Source #

pattern TAscr :: Term -> PolyType -> Term Source #

pattern TWild :: Term Source #

pattern TList :: [Term] -> Maybe (Ellipsis Term) -> Term Source #

data Quantifier Source #

A quantifier: λ, ∀, or ∃

Constructors

Lam 
Ex 
All 

Instances

Instances details
Eq Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

Data Quantifier 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) -> Quantifier -> c Quantifier #

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

toConstr :: Quantifier -> Constr #

dataTypeOf :: Quantifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

Show Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

Generic Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

Associated Types

type Rep Quantifier :: Type -> Type #

Alpha Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

Subst Type Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

type Rep Quantifier Source # 
Instance details

Defined in Disco.AST.Generic

type Rep Quantifier = D1 ('MetaData "Quantifier" "Disco.AST.Generic" "disco-0.1.5-Dj6M4uP9IofLLslCWcCyVQ" 'False) (C1 ('MetaCons "Lam" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ex" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "All" 'PrefixI 'False) (U1 :: Type -> Type)))

Telescopes

data Telescope b where Source #

A telescope is essentially a list, except that each item can bind names in the rest of the list.

Constructors

TelEmpty :: Telescope b

The empty telescope.

TelCons :: Rebind b (Telescope b) -> Telescope b

A binder of type b followed by zero or more b's. This b can bind variables in the subsequent b's.

Instances

Instances details
Pretty Branch Source #

Pretty-print a single branch in a case expression.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Branch -> Sem r Doc Source #

HasType ABranch Source # 
Instance details

Defined in Disco.AST.Typed

Subst t b => Subst t (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

Methods

isvar :: Telescope b -> Maybe (SubstName (Telescope b) t) #

isCoerceVar :: Telescope b -> Maybe (SubstCoerce (Telescope b) t) #

subst :: Name t -> t -> Telescope b -> Telescope b #

substs :: [(Name t, t)] -> Telescope b -> Telescope b #

Data b => Data (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

Methods

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

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

toConstr :: Telescope b -> Constr #

dataTypeOf :: Telescope b -> DataType #

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

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

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

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

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

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

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

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

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

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

Show b => Show (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

Generic (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

Associated Types

type Rep (Telescope b) :: Type -> Type #

Methods

from :: Telescope b -> Rep (Telescope b) x #

to :: Rep (Telescope b) x -> Telescope b #

Alpha b => Alpha (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

Pretty (Telescope Guard) Source #

Pretty-print the guards in a single branch of a case expression.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Telescope Guard -> Sem r Doc Source #

Pretty (Telescope Qual) Source #

Pretty-print the qualifiers in a comprehension.

Instance details

Defined in Disco.AST.Surface

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Telescope Qual -> Sem r Doc Source #

type Rep (Telescope b) Source # 
Instance details

Defined in Disco.AST.Generic

type Rep (Telescope b) = D1 ('MetaData "Telescope" "Disco.AST.Generic" "disco-0.1.5-Dj6M4uP9IofLLslCWcCyVQ" 'False) (C1 ('MetaCons "TelEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TelCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rebind b (Telescope b)))))

foldTelescope :: Alpha b => (b -> r -> r) -> r -> Telescope b -> r Source #

Fold a telescope given a combining function and a value to use for the empty telescope. Analogous to foldr for lists.

mapTelescope :: (Alpha a, Alpha b) => (a -> b) -> Telescope a -> Telescope b Source #

Apply a function to every item in a telescope.

toTelescope :: Alpha b => [b] -> Telescope b Source #

Convert a list to a telescope.

fromTelescope :: Alpha b => Telescope b -> [b] Source #

Convert a telescope to a list.

Expressions

data Side Source #

Injections into a sum type (inl or inr) have a "side" (L or R).

Constructors

L 
R 

Instances

Instances details
Bounded Side Source # 
Instance details

Defined in Disco.AST.Generic

Enum Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

succ :: Side -> Side #

pred :: Side -> Side #

toEnum :: Int -> Side #

fromEnum :: Side -> Int #

enumFrom :: Side -> [Side] #

enumFromThen :: Side -> Side -> [Side] #

enumFromTo :: Side -> Side -> [Side] #

enumFromThenTo :: Side -> Side -> Side -> [Side] #

Eq Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

Data Side 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) -> Side -> c Side #

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

toConstr :: Side -> Constr #

dataTypeOf :: Side -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

compare :: Side -> Side -> Ordering #

(<) :: Side -> Side -> Bool #

(<=) :: Side -> Side -> Bool #

(>) :: Side -> Side -> Bool #

(>=) :: Side -> Side -> Bool #

max :: Side -> Side -> Side #

min :: Side -> Side -> Side #

Show Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 
Instance details

Defined in Disco.AST.Generic

Associated Types

type Rep Side :: Type -> Type #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

Alpha Side Source # 
Instance details

Defined in Disco.AST.Generic

Pretty Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

pretty :: forall (r :: EffectRow). Members '[Reader PA, LFresh] r => Side -> Sem r Doc Source #

Subst t Side Source # 
Instance details

Defined in Disco.AST.Generic

Methods

isvar :: Side -> Maybe (SubstName Side t) #

isCoerceVar :: Side -> Maybe (SubstCoerce Side t) #

subst :: Name t -> t -> Side -> Side #

substs :: [(Name t, t)] -> Side -> Side #

type Rep Side Source # 
Instance details

Defined in Disco.AST.Generic

type Rep Side = D1 ('MetaData "Side" "Disco.AST.Generic" "disco-0.1.5-Dj6M4uP9IofLLslCWcCyVQ" 'False) (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R" 'PrefixI 'False) (U1 :: Type -> Type))

pattern TLink :: BOp -> Term -> Link Source #

Lists

pattern QBind :: Name Term -> Embed Term -> Qual Source #

pattern QGuard :: Embed Term -> Qual 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.5-Dj6M4uP9IofLLslCWcCyVQ" '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)))

data Ellipsis t where Source #

An ellipsis is an "omitted" part of a literal container (such as a list or set), of the form .. t. We don't have open-ended ellipses since everything is evaluated eagerly and hence containers must be finite.

Constructors

Until :: t -> Ellipsis t

Until represents an ellipsis with a given endpoint, as in [3 .. 20].

Instances

Instances details
Functor Ellipsis Source # 
Instance details

Defined in Disco.AST.Generic

Methods

fmap :: (a -> b) -> Ellipsis a -> Ellipsis b #

(<$) :: a -> Ellipsis b -> Ellipsis a #

Foldable Ellipsis Source # 
Instance details

Defined in Disco.AST.Generic

Methods

fold :: Monoid m => Ellipsis m -> m #

foldMap :: Monoid m => (a -> m) -> Ellipsis a -> m #

foldMap' :: Monoid m => (a -> m) -> Ellipsis a -> m #

foldr :: (a -> b -> b) -> b -> Ellipsis a -> b #

foldr' :: (a -> b -> b) -> b -> Ellipsis a -> b #

foldl :: (b -> a -> b) -> b -> Ellipsis a -> b #

foldl' :: (b -> a -> b) -> b -> Ellipsis a -> b #

foldr1 :: (a -> a -> a) -> Ellipsis a -> a #

foldl1 :: (a -> a -> a) -> Ellipsis a -> a #

toList :: Ellipsis a -> [a] #

null :: Ellipsis a -> Bool #

length :: Ellipsis a -> Int #

elem :: Eq a => a -> Ellipsis a -> Bool #

maximum :: Ord a => Ellipsis a -> a #

minimum :: Ord a => Ellipsis a -> a #

sum :: Num a => Ellipsis a -> a #

product :: Num a => Ellipsis a -> a #

Traversable Ellipsis Source # 
Instance details

Defined in Disco.AST.Generic

Methods

traverse :: Applicative f => (a -> f b) -> Ellipsis a -> f (Ellipsis b) #

sequenceA :: Applicative f => Ellipsis (f a) -> f (Ellipsis a) #

mapM :: Monad m => (a -> m b) -> Ellipsis a -> m (Ellipsis b) #

sequence :: Monad m => Ellipsis (m a) -> m (Ellipsis a) #

Subst a t => Subst a (Ellipsis t) Source # 
Instance details

Defined in Disco.AST.Generic

Methods

isvar :: Ellipsis t -> Maybe (SubstName (Ellipsis t) a) #

isCoerceVar :: Ellipsis t -> Maybe (SubstCoerce (Ellipsis t) a) #

subst :: Name a -> a -> Ellipsis t -> Ellipsis t #

substs :: [(Name a, a)] -> Ellipsis t -> Ellipsis t #

Data t => Data (Ellipsis t) 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) -> Ellipsis t -> c (Ellipsis t) #

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

toConstr :: Ellipsis t -> Constr #

dataTypeOf :: Ellipsis t -> DataType #

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

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

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

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

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

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

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

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

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

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

Show t => Show (Ellipsis t) Source # 
Instance details

Defined in Disco.AST.Generic

Methods

showsPrec :: Int -> Ellipsis t -> ShowS #

show :: Ellipsis t -> String #

showList :: [Ellipsis t] -> ShowS #

Generic (Ellipsis t) Source # 
Instance details

Defined in Disco.AST.Generic

Associated Types

type Rep (Ellipsis t) :: Type -> Type #

Methods

from :: Ellipsis t -> Rep (Ellipsis t) x #

to :: Rep (Ellipsis t) x -> Ellipsis t #

Alpha t => Alpha (Ellipsis t) Source # 
Instance details

Defined in Disco.AST.Generic

type Rep (Ellipsis t) Source # 
Instance details

Defined in Disco.AST.Generic

type Rep (Ellipsis t) = D1 ('MetaData "Ellipsis" "Disco.AST.Generic" "disco-0.1.5-Dj6M4uP9IofLLslCWcCyVQ" 'False) (C1 ('MetaCons "Until" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t)))

Case expressions and patterns

pattern GBool :: Embed Term -> Guard Source #

pattern GPat :: Embed Term -> Pattern -> Guard Source #

pattern GLet :: Binding -> Guard Source #

pattern PVar :: Name Term -> Pattern Source #

pattern PWild :: Pattern Source #

pattern PAscr :: Pattern -> Type -> Pattern Source #

pattern PUnit :: Pattern Source #

pattern PBool :: Bool -> Pattern Source #

pattern PChar :: Char -> Pattern Source #

pattern PString :: String -> Pattern Source #

pattern PTup :: [Pattern] -> Pattern Source #

pattern PInj :: Side -> Pattern -> Pattern Source #

pattern PNat :: Integer -> Pattern Source #

pattern PCons :: Pattern -> Pattern -> Pattern Source #

pattern PList :: [Pattern] -> Pattern Source #

pattern PAdd :: Side -> Pattern -> Term -> Pattern Source #

pattern PMul :: Side -> Pattern -> Term -> Pattern Source #

pattern PSub :: Pattern -> Term -> Pattern Source #

pattern PNeg :: Pattern -> Pattern Source #

pattern PFrac :: Pattern -> Pattern -> Pattern Source #