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

Disco.Context

Description

A *context* is a mapping from names to other things (such as types or values). This module defines a generic type of contexts which is used in many different places throughout the disco codebase.

Synopsis

Context type

data Ctx a b Source #

A context maps qualified names to things. In particular a Ctx a b maps qualified names for as to values of type b.

Instances

Instances details
Functor (Ctx a) Source # 
Instance details

Defined in Disco.Context

Methods

fmap :: (a0 -> b) -> Ctx a a0 -> Ctx a b #

(<$) :: a0 -> Ctx a b -> Ctx a a0 #

Foldable (Ctx a) Source # 
Instance details

Defined in Disco.Context

Methods

fold :: Monoid m => Ctx a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Ctx a a0 -> m #

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

foldr :: (a0 -> b -> b) -> b -> Ctx a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Ctx a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Ctx a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Ctx a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Ctx a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Ctx a a0 -> a0 #

toList :: Ctx a a0 -> [a0] #

null :: Ctx a a0 -> Bool #

length :: Ctx a a0 -> Int #

elem :: Eq a0 => a0 -> Ctx a a0 -> Bool #

maximum :: Ord a0 => Ctx a a0 -> a0 #

minimum :: Ord a0 => Ctx a a0 -> a0 #

sum :: Num a0 => Ctx a a0 -> a0 #

product :: Num a0 => Ctx a a0 -> a0 #

Traversable (Ctx a) Source # 
Instance details

Defined in Disco.Context

Methods

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

sequenceA :: Applicative f => Ctx a (f a0) -> f (Ctx a a0) #

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

sequence :: Monad m => Ctx a (m a0) -> m (Ctx a a0) #

Eq b => Eq (Ctx a b) Source # 
Instance details

Defined in Disco.Context

Methods

(==) :: Ctx a b -> Ctx a b -> Bool #

(/=) :: Ctx a b -> Ctx a b -> Bool #

Show b => Show (Ctx a b) Source # 
Instance details

Defined in Disco.Context

Methods

showsPrec :: Int -> Ctx a b -> ShowS #

show :: Ctx a b -> String #

showList :: [Ctx a b] -> ShowS #

Semigroup (Ctx a b) Source # 
Instance details

Defined in Disco.Context

Methods

(<>) :: Ctx a b -> Ctx a b -> Ctx a b #

sconcat :: NonEmpty (Ctx a b) -> Ctx a b #

stimes :: Integral b0 => b0 -> Ctx a b -> Ctx a b #

Monoid (Ctx a b) Source # 
Instance details

Defined in Disco.Context

Methods

mempty :: Ctx a b #

mappend :: Ctx a b -> Ctx a b -> Ctx a b #

mconcat :: [Ctx a b] -> Ctx a b #

Construction

emptyCtx :: Ctx a b Source #

The empty context.

singleCtx :: QName a -> b -> Ctx a b Source #

A singleton context, mapping a qualified name to a thing.

fromList :: [(QName a, b)] -> Ctx a b Source #

Create a context from a list of (qualified name, value) pairs.

ctxForModule :: ModuleName -> [(Name a, b)] -> Ctx a b Source #

Create a context for bindings from a single module.

localCtx :: [(Name a, b)] -> Ctx a b Source #

Create a context with local bindings.

Insertion

insert :: QName a -> b -> Ctx a b -> Ctx a b Source #

Insert a new binding into a context. The new binding shadows any old binding for the same qualified name.

extend :: Member (Reader (Ctx a b)) r => QName a -> b -> Sem r c -> Sem r c Source #

Run a computation under a context extended with a new binding. The new binding shadows any old binding for the same name.

extends :: Member (Reader (Ctx a b)) r => Ctx a b -> Sem r c -> Sem r c Source #

Run a computation in a context extended with an additional context. Bindings in the additional context shadow any bindings with the same names in the existing context.

Query

null :: Ctx a b -> Bool Source #

Check if a context is empty.

lookup :: Member (Reader (Ctx a b)) r => QName a -> Sem r (Maybe b) Source #

Look up a qualified name in an ambient context.

lookup' :: QName a -> Ctx a b -> Maybe b Source #

Look up a qualified name in a context.

lookupNonLocal :: Member (Reader (Ctx a b)) r => Name a -> Sem r [(ModuleName, b)] Source #

Look up all the non-local bindings of a name in an ambient context.

lookupNonLocal' :: Name a -> Ctx a b -> [(ModuleName, b)] Source #

Look up all the non-local bindings of a name in a context.

lookupAll :: Member (Reader (Ctx a b)) r => Name a -> Sem r [(QName a, b)] Source #

Look up all the bindings of an (unqualified) name in an ambient context.

lookupAll' :: Name a -> Ctx a b -> [(QName a, b)] Source #

Look up all the bindings of an (unqualified) name in a context.

Conversion

names :: Ctx a b -> [Name a] Source #

Return a list of the names defined by the context.

elems :: Ctx a b -> [b] Source #

Return a list of all the values bound by the context.

assocs :: Ctx a b -> [(QName a, b)] Source #

Return a list of the qualified name-value associations in the context.

keysSet :: Ctx a b -> Set (QName a) Source #

Return a set of all qualified names in the context.

Traversal

coerceKeys :: Ctx a1 b -> Ctx a2 b Source #

Coerce the type of the qualified name keys in a context.

restrictKeys :: Ctx a b -> Set (QName a) -> Ctx a b Source #

Restrict a context to only the keys in the given set.

Combination

joinCtx :: Ctx a b -> Ctx a b -> Ctx a b Source #

Join two contexts (left-biased, i.e. if the same qualified name exists in both contexts, the result will use the value from the first context, and throw away the value from the second.).

joinCtxs :: [Ctx a b] -> Ctx a b Source #

Join a list of contexts (left-biased).

Filter

filter :: (b -> Bool) -> Ctx a b -> Ctx a b Source #

Filter a context using a predicate.