rebound-0.1.1.0: A variable binding library based on well-scoped de Bruijn indices.
Safe HaskellNone
LanguageGHC2021

Data.Scoped.Classes

Description

These classes provide access to scoped versions of higher-kinded classes such as Functor/Foldable etc. All instances of this class should be coercible to existing instances of these classes. (Which are used in the default definitions.)

Synopsis

Documentation

newtype ((a :: k -> Type) ~> (b :: k -> Type)) (n :: k) Source #

A scoped function (i.e., a function whose input & output are scoped).

Constructors

MkArr (a n -> b n) 

Instances

Instances details
(CoArbitrary (a n), Arbitrary (b n)) => Arbitrary ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

arbitrary :: Gen ((a ~> b) n) #

shrink :: (a ~> b) n -> [(a ~> b) n] #

(Arbitrary (a n), CoArbitrary (b n)) => CoArbitrary ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

coarbitrary :: (a ~> b) n -> Gen b0 -> Gen b0 #

(Arbitrary (a n), Show (a n), Testable (b n)) => Testable ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

property :: (a ~> b) n -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> (a ~> b) n) -> Property #

Monoid (b n) => Monoid ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

mempty :: (a ~> b) n #

mappend :: (a ~> b) n -> (a ~> b) n -> (a ~> b) n #

mconcat :: [(a ~> b) n] -> (a ~> b) n #

Semigroup (b n) => Semigroup ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

(<>) :: (a ~> b) n -> (a ~> b) n -> (a ~> b) n #

sconcat :: NonEmpty ((a ~> b) n) -> (a ~> b) n #

stimes :: Integral b0 => b0 -> (a ~> b) n -> (a ~> b) n #

Generic ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Associated Types

type Rep ((a ~> b) n) 
Instance details

Defined in Data.Scoped.Classes

type Rep ((a ~> b) n) = D1 ('MetaData "~>" "Data.Scoped.Classes" "rebound-0.1.1.0-5YS3Pj5eRoJLTw0p7qb7Vu" 'True) (C1 ('MetaCons "MkArr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a n -> b n))))

Methods

from :: (a ~> b) n -> Rep ((a ~> b) n) x #

to :: Rep ((a ~> b) n) x -> (a ~> b) n #

NFData ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

Methods

rnf :: (a ~> b) n -> () #

type Rep ((a ~> b) n) Source # 
Instance details

Defined in Data.Scoped.Classes

type Rep ((a ~> b) n) = D1 ('MetaData "~>" "Data.Scoped.Classes" "rebound-0.1.1.0-5YS3Pj5eRoJLTw0p7qb7Vu" 'True) (C1 ('MetaCons "MkArr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a n -> b n))))

class (forall (a :: k -> Type) (n :: k). Coercible (f a n) (k1 (a n)), Functor k1) => ScopedFunctor (k1 :: Type -> Type) (f :: (k -> Type) -> k -> Type) | f -> k1 where Source #

Scoped Functor.

Minimal complete definition

Nothing

Methods

fmap :: forall a (n :: k) b. Functor k1 => (a n -> b n) -> f a n -> f b n Source #

Instances

Instances details
ScopedFunctor Maybe (Maybe :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.Maybe

Methods

fmap :: forall a (n :: k) b. Functor Maybe => (a n -> b n) -> Maybe a n -> Maybe b n Source #

ScopedFunctor [] (List :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.List

Methods

fmap :: forall a (n :: k) b. Functor [] => (a n -> b n) -> List a n -> List b n Source #

class (forall (a :: k -> Type) (n :: k). Coercible (f a n) (k1 (a n)), Foldable k1) => ScopedFoldable (k1 :: Type -> Type) (f :: (k -> Type) -> k -> Type) | f -> k1 where Source #

Scoped Foldable.

Minimal complete definition

Nothing

Methods

fold :: forall a (n :: k). Monoid (a n) => f a n -> a n Source #

foldMap :: forall m a (n :: k). Monoid m => (a n -> m) -> f a n -> m Source #

foldMap' :: forall m a (n :: k). Monoid m => (a n -> m) -> f a n -> m Source #

foldr :: forall a (n :: k) b. (a n -> b -> b) -> b -> f a n -> b Source #

foldr' :: forall a (n :: k) b. (a n -> b -> b) -> b -> f a n -> b Source #

foldl :: forall b a (n :: k). (b -> a n -> b) -> b -> f a n -> b Source #

foldl' :: forall b a (n :: k). (b -> a n -> b) -> b -> f a n -> b Source #

foldr1 :: forall a (n :: k). (a n -> a n -> a n) -> f a n -> a n Source #

foldl1 :: forall a (n :: k). (a n -> a n -> a n) -> f a n -> a n Source #

null :: forall (a :: k -> Type) (n :: k). f a n -> Bool Source #

length :: forall (a :: k -> Type) (n :: k). f a n -> Int Source #

elem :: forall a (n :: k). Eq (a n) => a n -> f a n -> Bool Source #

maximum :: forall a (n :: k). Ord (a n) => f a n -> a n Source #

minimum :: forall a (n :: k). Ord (a n) => f a n -> a n Source #

sum :: forall a (n :: k). Num (a n) => f a n -> a n Source #

product :: forall a (n :: k). Num (a n) => f a n -> a n Source #

any :: forall a (n :: k). (a n -> Bool) -> f a n -> Bool Source #

all :: forall a (n :: k). (a n -> Bool) -> f a n -> Bool Source #

mapM_ :: forall m a (n :: k) b. Monad m => (a n -> m b) -> f a n -> m () Source #

Instances

Instances details
ScopedFoldable Maybe (Maybe :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.Maybe

Methods

fold :: forall a (n :: k). Monoid (a n) => Maybe a n -> a n Source #

foldMap :: forall m a (n :: k). Monoid m => (a n -> m) -> Maybe a n -> m Source #

foldMap' :: forall m a (n :: k). Monoid m => (a n -> m) -> Maybe a n -> m Source #

foldr :: forall a (n :: k) b. (a n -> b -> b) -> b -> Maybe a n -> b Source #

foldr' :: forall a (n :: k) b. (a n -> b -> b) -> b -> Maybe a n -> b Source #

foldl :: forall b a (n :: k). (b -> a n -> b) -> b -> Maybe a n -> b Source #

foldl' :: forall b a (n :: k). (b -> a n -> b) -> b -> Maybe a n -> b Source #

foldr1 :: forall a (n :: k). (a n -> a n -> a n) -> Maybe a n -> a n Source #

foldl1 :: forall a (n :: k). (a n -> a n -> a n) -> Maybe a n -> a n Source #

null :: forall (a :: k -> Type) (n :: k). Maybe a n -> Bool Source #

length :: forall (a :: k -> Type) (n :: k). Maybe a n -> Int Source #

elem :: forall a (n :: k). Eq (a n) => a n -> Maybe a n -> Bool Source #

maximum :: forall a (n :: k). Ord (a n) => Maybe a n -> a n Source #

minimum :: forall a (n :: k). Ord (a n) => Maybe a n -> a n Source #

sum :: forall a (n :: k). Num (a n) => Maybe a n -> a n Source #

product :: forall a (n :: k). Num (a n) => Maybe a n -> a n Source #

any :: forall a (n :: k). (a n -> Bool) -> Maybe a n -> Bool Source #

all :: forall a (n :: k). (a n -> Bool) -> Maybe a n -> Bool Source #

mapM_ :: forall m a (n :: k) b. Monad m => (a n -> m b) -> Maybe a n -> m () Source #

ScopedFoldable [] (List :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.List

Methods

fold :: forall a (n :: k). Monoid (a n) => List a n -> a n Source #

foldMap :: forall m a (n :: k). Monoid m => (a n -> m) -> List a n -> m Source #

foldMap' :: forall m a (n :: k). Monoid m => (a n -> m) -> List a n -> m Source #

foldr :: forall a (n :: k) b. (a n -> b -> b) -> b -> List a n -> b Source #

foldr' :: forall a (n :: k) b. (a n -> b -> b) -> b -> List a n -> b Source #

foldl :: forall b a (n :: k). (b -> a n -> b) -> b -> List a n -> b Source #

foldl' :: forall b a (n :: k). (b -> a n -> b) -> b -> List a n -> b Source #

foldr1 :: forall a (n :: k). (a n -> a n -> a n) -> List a n -> a n Source #

foldl1 :: forall a (n :: k). (a n -> a n -> a n) -> List a n -> a n Source #

null :: forall (a :: k -> Type) (n :: k). List a n -> Bool Source #

length :: forall (a :: k -> Type) (n :: k). List a n -> Int Source #

elem :: forall a (n :: k). Eq (a n) => a n -> List a n -> Bool Source #

maximum :: forall a (n :: k). Ord (a n) => List a n -> a n Source #

minimum :: forall a (n :: k). Ord (a n) => List a n -> a n Source #

sum :: forall a (n :: k). Num (a n) => List a n -> a n Source #

product :: forall a (n :: k). Num (a n) => List a n -> a n Source #

any :: forall a (n :: k). (a n -> Bool) -> List a n -> Bool Source #

all :: forall a (n :: k). (a n -> Bool) -> List a n -> Bool Source #

mapM_ :: forall m a (n :: k) b. Monad m => (a n -> m b) -> List a n -> m () Source #

class (forall (a :: k -> Type) (n :: k). Coercible (t a n) (k1 (a n)), Traversable k1) => ScopedTraversable (k1 :: Type -> Type) (t :: (k -> Type) -> k -> Type) | t -> k1 where Source #

Scoped Traversable.

Minimal complete definition

Nothing

Methods

traverse :: forall a b (n :: k) f. Applicative f => (a n -> f (b n)) -> t a n -> f (t b n) Source #

mapM :: forall m a (n :: k) b. Monad m => (a n -> m (b n)) -> t a n -> m (t b n) Source #

Instances

Instances details
ScopedTraversable Maybe (Maybe :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.Maybe

Methods

traverse :: forall a b (n :: k) f. Applicative f => (a n -> f (b n)) -> Maybe a n -> f (Maybe b n) Source #

mapM :: forall m a (n :: k) b. Monad m => (a n -> m (b n)) -> Maybe a n -> m (Maybe b n) Source #

ScopedTraversable [] (List :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.List

Methods

traverse :: forall a b (n :: k) f. Applicative f => (a n -> f (b n)) -> List a n -> f (List b n) Source #

mapM :: forall m a (n :: k) b. Monad m => (a n -> m (b n)) -> List a n -> m (List b n) Source #

class (forall (a :: k -> Type) (n :: k). Coercible (t a n) (k1 (a n)), Applicative k1) => ScopedApplicative (k1 :: Type -> Type) (t :: (k -> Type) -> k -> Type) | t -> k1 where Source #

Scoped Applicative.

Minimal complete definition

Nothing

Methods

pure :: forall a (n :: k). a n -> t a n Source #

(<*>) :: forall (a :: k -> Type) (b :: k -> Type) (n :: k). t (a ~> b) n -> t a n -> t b n Source #

Instances

Instances details
ScopedApplicative Maybe (Maybe :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.Maybe

Methods

pure :: forall a (n :: k). a n -> Maybe a n Source #

(<*>) :: forall (a :: k -> Type) (b :: k -> Type) (n :: k). Maybe (a ~> b) n -> Maybe a n -> Maybe b n Source #

ScopedApplicative [] (List :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.List

Methods

pure :: forall a (n :: k). a n -> List a n Source #

(<*>) :: forall (a :: k -> Type) (b :: k -> Type) (n :: k). List (a ~> b) n -> List a n -> List b n Source #

class (forall (a :: k -> Type) (n :: k). Coercible (t a n) (k1 (a n)), Monad k1, ScopedApplicative k1 t) => ScopedMonad (k1 :: Type -> Type) (t :: (k -> Type) -> k -> Type) | t -> k1 where Source #

Scoped Monad.

Minimal complete definition

Nothing

Methods

return :: forall a (n :: k). a n -> t a n Source #

(>>=) :: forall a (n :: k) (b :: k -> Type) (m :: k). t a n -> (a n -> t b m) -> t b m Source #

Instances

Instances details
ScopedMonad Maybe (Maybe :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.Maybe

Methods

return :: forall a (n :: k). a n -> Maybe a n Source #

(>>=) :: forall a (n :: k) (b :: k -> Type) (m :: k). Maybe a n -> (a n -> Maybe b m) -> Maybe b m Source #

ScopedMonad [] (List :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.Scoped.List

Methods

return :: forall a (n :: k). a n -> List a n Source #

(>>=) :: forall a (n :: k) (b :: k -> Type) (m :: k). List a n -> (a n -> List b m) -> List b m Source #