rzk-0.7.4: An experimental proof assistant for synthetic ∞-categories
Safe HaskellSafe-Inferred
LanguageHaskell2010

Free.Scoped

Documentation

data Inc var Source #

Constructors

Z 
S var 

Instances

Instances details
Foldable Inc Source # 
Instance details

Defined in Free.Scoped

Methods

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

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

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

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

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

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

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

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

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

toList :: Inc a -> [a] #

null :: Inc a -> Bool #

length :: Inc a -> Int #

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

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

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

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

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

Traversable Inc Source # 
Instance details

Defined in Free.Scoped

Methods

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

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

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

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

Functor Inc Source # 
Instance details

Defined in Free.Scoped

Methods

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

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

Show var => Show (Inc var) Source # 
Instance details

Defined in Free.Scoped

Methods

showsPrec :: Int -> Inc var -> ShowS #

show :: Inc var -> String #

showList :: [Inc var] -> ShowS #

Eq var => Eq (Inc var) Source # 
Instance details

Defined in Free.Scoped

Methods

(==) :: Inc var -> Inc var -> Bool #

(/=) :: Inc var -> Inc var -> Bool #

type Scope term var = term (Inc var) Source #

instantiate :: Monad f => f a -> f (Inc a) -> f a Source #

abstract :: (Eq a, Functor f) => a -> f a -> f (Inc a) Source #

data FS t a Source #

Constructors

Pure a 
Free (t (Scope (FS t) a) (FS t a)) 

Instances

Instances details
IsString Term' Source # 
Instance details

Defined in Language.Rzk.Free.Syntax

Methods

fromString :: String -> Term' #

IsString TermT' Source #

Parse and unsafeInferStandalone'.

Instance details

Defined in Rzk.TypeCheck

Methods

fromString :: String -> TermT' #

Show Term' Source # 
Instance details

Defined in Language.Rzk.Free.Syntax

Methods

showsPrec :: Int -> Term' -> ShowS #

show :: Term' -> String #

showList :: [Term'] -> ShowS #

Show TermT' Source # 
Instance details

Defined in Language.Rzk.Free.Syntax

Bifoldable t => Foldable (FS t) Source # 
Instance details

Defined in Free.Scoped

Methods

fold :: Monoid m => FS t m -> m #

foldMap :: Monoid m => (a -> m) -> FS t a -> m #

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

foldr :: (a -> b -> b) -> b -> FS t a -> b #

foldr' :: (a -> b -> b) -> b -> FS t a -> b #

foldl :: (b -> a -> b) -> b -> FS t a -> b #

foldl' :: (b -> a -> b) -> b -> FS t a -> b #

foldr1 :: (a -> a -> a) -> FS t a -> a #

foldl1 :: (a -> a -> a) -> FS t a -> a #

toList :: FS t a -> [a] #

null :: FS t a -> Bool #

length :: FS t a -> Int #

elem :: Eq a => a -> FS t a -> Bool #

maximum :: Ord a => FS t a -> a #

minimum :: Ord a => FS t a -> a #

sum :: Num a => FS t a -> a #

product :: Num a => FS t a -> a #

Bitraversable t => Traversable (FS t) Source # 
Instance details

Defined in Free.Scoped

Methods

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

sequenceA :: Applicative f => FS t (f a) -> f (FS t a) #

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

sequence :: Monad m => FS t (m a) -> m (FS t a) #

Bifunctor t => Applicative (FS t) Source # 
Instance details

Defined in Free.Scoped

Methods

pure :: a -> FS t a #

(<*>) :: FS t (a -> b) -> FS t a -> FS t b #

liftA2 :: (a -> b -> c) -> FS t a -> FS t b -> FS t c #

(*>) :: FS t a -> FS t b -> FS t b #

(<*) :: FS t a -> FS t b -> FS t a #

Bifunctor t => Functor (FS t) Source # 
Instance details

Defined in Free.Scoped

Methods

fmap :: (a -> b) -> FS t a -> FS t b #

(<$) :: a -> FS t b -> FS t a #

Bifunctor t => Monad (FS t) Source # 
Instance details

Defined in Free.Scoped

Methods

(>>=) :: FS t a -> (a -> FS t b) -> FS t b #

(>>) :: FS t a -> FS t b -> FS t b #

return :: a -> FS t a #

(Eq a, forall x y. (Eq x, Eq y) => Eq (t x y)) => Eq (FS t a) Source # 
Instance details

Defined in Free.Scoped

Methods

(==) :: FS t a -> FS t a -> Bool #

(/=) :: FS t a -> FS t a -> Bool #

data Sum f g scope term Source #

Constructors

InL (f scope term) 
InR (g scope term) 

Instances

Instances details
(Bifoldable f, Bifoldable g) => Bifoldable (Sum f g) Source # 
Instance details

Defined in Free.Scoped

Methods

bifold :: Monoid m => Sum f g m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Sum f g a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Sum f g a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Sum f g a b -> c #

(Bifunctor f, Bifunctor g) => Bifunctor (Sum f g) Source # 
Instance details

Defined in Free.Scoped

Methods

bimap :: (a -> b) -> (c -> d) -> Sum f g a c -> Sum f g b d #

first :: (a -> b) -> Sum f g a c -> Sum f g b c #

second :: (b -> c) -> Sum f g a b -> Sum f g a c #

(Bitraversable f, Bitraversable g) => Bitraversable (Sum f g) Source # 
Instance details

Defined in Free.Scoped

Methods

bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Sum f g a b -> f0 (Sum f g c d) #

(Foldable (f scope), Foldable (g scope)) => Foldable (Sum f g scope) Source # 
Instance details

Defined in Free.Scoped

Methods

fold :: Monoid m => Sum f g scope m -> m #

foldMap :: Monoid m => (a -> m) -> Sum f g scope a -> m #

foldMap' :: Monoid m => (a -> m) -> Sum f g scope a -> m #

foldr :: (a -> b -> b) -> b -> Sum f g scope a -> b #

foldr' :: (a -> b -> b) -> b -> Sum f g scope a -> b #

foldl :: (b -> a -> b) -> b -> Sum f g scope a -> b #

foldl' :: (b -> a -> b) -> b -> Sum f g scope a -> b #

foldr1 :: (a -> a -> a) -> Sum f g scope a -> a #

foldl1 :: (a -> a -> a) -> Sum f g scope a -> a #

toList :: Sum f g scope a -> [a] #

null :: Sum f g scope a -> Bool #

length :: Sum f g scope a -> Int #

elem :: Eq a => a -> Sum f g scope a -> Bool #

maximum :: Ord a => Sum f g scope a -> a #

minimum :: Ord a => Sum f g scope a -> a #

sum :: Num a => Sum f g scope a -> a #

product :: Num a => Sum f g scope a -> a #

(Traversable (f scope), Traversable (g scope)) => Traversable (Sum f g scope) Source # 
Instance details

Defined in Free.Scoped

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Sum f g scope a -> f0 (Sum f g scope b) #

sequenceA :: Applicative f0 => Sum f g scope (f0 a) -> f0 (Sum f g scope a) #

mapM :: Monad m => (a -> m b) -> Sum f g scope a -> m (Sum f g scope b) #

sequence :: Monad m => Sum f g scope (m a) -> m (Sum f g scope a) #

(Functor (f scope), Functor (g scope)) => Functor (Sum f g scope) Source # 
Instance details

Defined in Free.Scoped

Methods

fmap :: (a -> b) -> Sum f g scope a -> Sum f g scope b #

(<$) :: a -> Sum f g scope b -> Sum f g scope a #

Generic (Sum f g scope term) Source # 
Instance details

Defined in Free.Scoped

Associated Types

type Rep (Sum f g scope term) :: Type -> Type #

Methods

from :: Sum f g scope term -> Rep (Sum f g scope term) x #

to :: Rep (Sum f g scope term) x -> Sum f g scope term #

type Rep (Sum f g scope term) Source # 
Instance details

Defined in Free.Scoped

type Rep (Sum f g scope term) = D1 ('MetaData "Sum" "Free.Scoped" "rzk-0.7.4-7FvkIVXfwQV9exNV6IKg4P" 'False) (C1 ('MetaCons "InL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f scope term))) :+: C1 ('MetaCons "InR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g scope term))))

type (:+:) = Sum Source #

data Empty scope term Source #

Instances

Instances details
Bifoldable Empty Source # 
Instance details

Defined in Free.Scoped

Methods

bifold :: Monoid m => Empty m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Empty a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Empty a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Empty a b -> c #

Bifunctor Empty Source # 
Instance details

Defined in Free.Scoped

Methods

bimap :: (a -> b) -> (c -> d) -> Empty a c -> Empty b d #

first :: (a -> b) -> Empty a c -> Empty b c #

second :: (b -> c) -> Empty a b -> Empty a c #

Bitraversable Empty Source # 
Instance details

Defined in Free.Scoped

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Empty a b -> f (Empty c d) #

Foldable (Empty scope) Source # 
Instance details

Defined in Free.Scoped

Methods

fold :: Monoid m => Empty scope m -> m #

foldMap :: Monoid m => (a -> m) -> Empty scope a -> m #

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

foldr :: (a -> b -> b) -> b -> Empty scope a -> b #

foldr' :: (a -> b -> b) -> b -> Empty scope a -> b #

foldl :: (b -> a -> b) -> b -> Empty scope a -> b #

foldl' :: (b -> a -> b) -> b -> Empty scope a -> b #

foldr1 :: (a -> a -> a) -> Empty scope a -> a #

foldl1 :: (a -> a -> a) -> Empty scope a -> a #

toList :: Empty scope a -> [a] #

null :: Empty scope a -> Bool #

length :: Empty scope a -> Int #

elem :: Eq a => a -> Empty scope a -> Bool #

maximum :: Ord a => Empty scope a -> a #

minimum :: Ord a => Empty scope a -> a #

sum :: Num a => Empty scope a -> a #

product :: Num a => Empty scope a -> a #

Traversable (Empty scope) Source # 
Instance details

Defined in Free.Scoped

Methods

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

sequenceA :: Applicative f => Empty scope (f a) -> f (Empty scope a) #

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

sequence :: Monad m => Empty scope (m a) -> m (Empty scope a) #

Functor (Empty scope) Source # 
Instance details

Defined in Free.Scoped

Methods

fmap :: (a -> b) -> Empty scope a -> Empty scope b #

(<$) :: a -> Empty scope b -> Empty scope a #

data AnnF ann term scope typedTerm Source #

Constructors

AnnF 

Fields

  • annF :: ann typedTerm
     
  • termF :: term scope typedTerm
     

Instances

Instances details
IsString TermT' Source #

Parse and unsafeInferStandalone'.

Instance details

Defined in Rzk.TypeCheck

Methods

fromString :: String -> TermT' #

Show TermT' Source # 
Instance details

Defined in Language.Rzk.Free.Syntax

Bifoldable term => Bifoldable (AnnF ann term) Source #

Important: does not fold over the annF component!

Instance details

Defined in Free.Scoped

Methods

bifold :: Monoid m => AnnF ann term m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> AnnF ann term a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> AnnF ann term a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> AnnF ann term a b -> c #

(Functor ann, Bifunctor term) => Bifunctor (AnnF ann term) Source # 
Instance details

Defined in Free.Scoped

Methods

bimap :: (a -> b) -> (c -> d) -> AnnF ann term a c -> AnnF ann term b d #

first :: (a -> b) -> AnnF ann term a c -> AnnF ann term b c #

second :: (b -> c) -> AnnF ann term a b -> AnnF ann term a c #

(Traversable ann, Bitraversable term) => Bitraversable (AnnF ann term) Source # 
Instance details

Defined in Free.Scoped

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> AnnF ann term a b -> f (AnnF ann term c d) #

(Functor ann, Functor (term scope)) => Functor (AnnF ann term scope) Source # 
Instance details

Defined in Free.Scoped

Methods

fmap :: (a -> b) -> AnnF ann term scope a -> AnnF ann term scope b #

(<$) :: a -> AnnF ann term scope b -> AnnF ann term scope a #

(Show (ann typedTerm), Show (term scope typedTerm)) => Show (AnnF ann term scope typedTerm) Source # 
Instance details

Defined in Free.Scoped

Methods

showsPrec :: Int -> AnnF ann term scope typedTerm -> ShowS #

show :: AnnF ann term scope typedTerm -> String #

showList :: [AnnF ann term scope typedTerm] -> ShowS #

Eq (term scope typedTerm) => Eq (AnnF ann term scope typedTerm) Source #

Important: does not compare the annF component!

Instance details

Defined in Free.Scoped

Methods

(==) :: AnnF ann term scope typedTerm -> AnnF ann term scope typedTerm -> Bool #

(/=) :: AnnF ann term scope typedTerm -> AnnF ann term scope typedTerm -> Bool #

transFS :: Bifunctor term => (forall s t. term s t -> term' s t) -> FS term a -> FS term' a Source #

untyped :: (Functor ann, Bifunctor term) => FS (AnnF ann term) a -> FS term a Source #

pattern ExtE :: ext (Scope (FS (t :+: ext)) a) (FS (t :+: ext) a) -> FS (t :+: ext) a Source #

substitute :: Bifunctor t => FS t a -> Scope (FS t) a -> FS t a Source #