applicable-0.4.1.0: A class for things that can be applied
Copyrightⓒ 2022 Anselm Schüler
LicenseMIT
Maintainermail@anselmschueler.com
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • GeneralizedNewtypeDeriving

Data.Applicable

Description

The Applicable class with its operator ($*). You will likely need the FlexibleContexts extension to use this module’s instances.

Synopsis

Documentation

class Applicable f a b | f a -> b where Source #

A class for types whose values can be applied. Instances are required to be uniquely determined by the applied and applied-to type.

Methods

($*) :: f -> a -> b Source #

Apply a value to another value, producing a result.

Instances

Instances details
Applicable ChurchBool a (a -> a) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchBool -> a -> a -> a Source #

Semigroup a => Applicable (GroupAction a) a a Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: GroupAction a -> a -> a Source #

Applicable (ApplyTo a) (a -> b) b Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyTo a -> (a -> b) -> b Source #

Integral a => Applicable (ChurchNumeral a) (a -> a) (a -> a) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchNumeral a -> (a -> a) -> a -> a Source #

Applicable (a -> b) a b Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: (a -> b) -> a -> b Source #

Functor f => Applicable (ApplyMap a b) (f a) (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyMap a b -> f a -> f b Source #

Applicable (ChurchTuple a b) (a -> b -> c) c Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchTuple a b -> (a -> b -> c) -> c Source #

Functor f => Applicable (FlapApply f a b) a (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: FlapApply f a b -> a -> f b Source #

Applicative f => Applicable (ApplyAp f a b) (f a) (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyAp f a b -> f a -> f b Source #

Monad m => Applicable (ApplyBind m a b) (m a) (m b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyBind m a b -> m a -> m b Source #

Bifunctor f => Applicable (BiFlapApply f a b c) a (f b c) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: BiFlapApply f a b c -> a -> f b c Source #

newtype ApplyTo a Source #

A wrapper for values. Can be applied to a function, applying the function to the value.

Constructors

AppTo 

Fields

Instances

Instances details
Foldable ApplyTo Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

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

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

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

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

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

toList :: ApplyTo a -> [a] #

null :: ApplyTo a -> Bool #

length :: ApplyTo a -> Int #

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

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

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

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

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

Traversable ApplyTo Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

Functor ApplyTo Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

Data a => Data (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

toConstr :: ApplyTo a -> Constr #

dataTypeOf :: ApplyTo a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ApplyTo a) :: Type -> Type #

Methods

from :: ApplyTo a -> Rep (ApplyTo a) x #

to :: Rep (ApplyTo a) x -> ApplyTo a #

Ix a => Ix (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Methods

range :: (ApplyTo a, ApplyTo a) -> [ApplyTo a] #

index :: (ApplyTo a, ApplyTo a) -> ApplyTo a -> Int #

unsafeIndex :: (ApplyTo a, ApplyTo a) -> ApplyTo a -> Int #

inRange :: (ApplyTo a, ApplyTo a) -> ApplyTo a -> Bool #

rangeSize :: (ApplyTo a, ApplyTo a) -> Int #

unsafeRangeSize :: (ApplyTo a, ApplyTo a) -> Int #

Read a => Read (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Show a => Show (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Methods

showsPrec :: Int -> ApplyTo a -> ShowS #

show :: ApplyTo a -> String #

showList :: [ApplyTo a] -> ShowS #

Eq a => Eq (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Methods

(==) :: ApplyTo a -> ApplyTo a -> Bool #

(/=) :: ApplyTo a -> ApplyTo a -> Bool #

Ord a => Ord (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

Methods

compare :: ApplyTo a -> ApplyTo a -> Ordering #

(<) :: ApplyTo a -> ApplyTo a -> Bool #

(<=) :: ApplyTo a -> ApplyTo a -> Bool #

(>) :: ApplyTo a -> ApplyTo a -> Bool #

(>=) :: ApplyTo a -> ApplyTo a -> Bool #

max :: ApplyTo a -> ApplyTo a -> ApplyTo a #

min :: ApplyTo a -> ApplyTo a -> ApplyTo a #

Applicable (ApplyTo a) (a -> b) b Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyTo a -> (a -> b) -> b Source #

type Rep (ApplyTo a) Source # 
Instance details

Defined in Data.Applicable

type Rep (ApplyTo a) = D1 ('MetaData "ApplyTo" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "AppTo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAppTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype FlapApply f a b Source #

A wrapper for functions wrapped in a Functor. Can be applied to a value, fmap-ing the application over the Functor.

This nomenclature is borrowed from relude.

Constructors

FlApp 

Fields

Instances

Instances details
Functor f => Functor (FlapApply f a) Source # 
Instance details

Defined in Data.Applicable

Methods

fmap :: (a0 -> b) -> FlapApply f a a0 -> FlapApply f a b #

(<$) :: a0 -> FlapApply f a b -> FlapApply f a a0 #

Generic (FlapApply f a b) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (FlapApply f a b) :: Type -> Type #

Methods

from :: FlapApply f a b -> Rep (FlapApply f a b) x #

to :: Rep (FlapApply f a b) x -> FlapApply f a b #

Functor f => Applicable (FlapApply f a b) a (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: FlapApply f a b -> a -> f b Source #

type Rep (FlapApply f a b) Source # 
Instance details

Defined in Data.Applicable

type Rep (FlapApply f a b) = D1 ('MetaData "FlapApply" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "FlApp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFlApp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (a -> b)))))

newtype BiFlapApply f a b c Source #

A wrapper for functions wrapped in a Bifunctor. Can be applied to a value, bimap-ing the application over both fields.

Constructors

BiFlApp 

Fields

Instances

Instances details
Generic (BiFlapApply f a b c) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (BiFlapApply f a b c) :: Type -> Type #

Methods

from :: BiFlapApply f a b c -> Rep (BiFlapApply f a b c) x #

to :: Rep (BiFlapApply f a b c) x -> BiFlapApply f a b c #

Bifunctor f => Applicable (BiFlapApply f a b c) a (f b c) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: BiFlapApply f a b c -> a -> f b c Source #

type Rep (BiFlapApply f a b c) Source # 
Instance details

Defined in Data.Applicable

type Rep (BiFlapApply f a b c) = D1 ('MetaData "BiFlapApply" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "BiFlApp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBiFlApp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (a -> b) (a -> c)))))

newtype ApplyMap a b Source #

A wrapper for functions. Can be applied to a Functor, fmap-ing the function over the inner values.

Constructors

AppMap 

Fields

Instances

Instances details
Functor (ApplyMap a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

Generic (ApplyMap a b) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ApplyMap a b) :: Type -> Type #

Methods

from :: ApplyMap a b -> Rep (ApplyMap a b) x #

to :: Rep (ApplyMap a b) x -> ApplyMap a b #

Functor f => Applicable (ApplyMap a b) (f a) (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyMap a b -> f a -> f b Source #

type Rep (ApplyMap a b) Source # 
Instance details

Defined in Data.Applicable

type Rep (ApplyMap a b) = D1 ('MetaData "ApplyMap" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "AppMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAppMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> b))))

newtype ApplyAp f a b Source #

A wrapper for functions in an applicative functor. Can be applied to an Applicative functor, (<*>)-ing it on it.

Constructors

AppAp 

Fields

Instances

Instances details
Functor f => Functor (ApplyAp f a) Source # 
Instance details

Defined in Data.Applicable

Methods

fmap :: (a0 -> b) -> ApplyAp f a a0 -> ApplyAp f a b #

(<$) :: a0 -> ApplyAp f a b -> ApplyAp f a a0 #

Generic (ApplyAp f a b) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ApplyAp f a b) :: Type -> Type #

Methods

from :: ApplyAp f a b -> Rep (ApplyAp f a b) x #

to :: Rep (ApplyAp f a b) x -> ApplyAp f a b #

Applicative f => Applicable (ApplyAp f a b) (f a) (f b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyAp f a b -> f a -> f b Source #

type Rep (ApplyAp f a b) Source # 
Instance details

Defined in Data.Applicable

type Rep (ApplyAp f a b) = D1 ('MetaData "ApplyAp" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "AppAp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAppAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (a -> b)))))

newtype ApplyBind m a b Source #

A wrapper for Kleisli arrows. Can be applied to a Monad, (>>=)-ing it on it.

Constructors

AppBind 

Fields

Instances

Instances details
Functor m => Functor (ApplyBind m a) Source # 
Instance details

Defined in Data.Applicable

Methods

fmap :: (a0 -> b) -> ApplyBind m a a0 -> ApplyBind m a b #

(<$) :: a0 -> ApplyBind m a b -> ApplyBind m a a0 #

Generic (ApplyBind m a b) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ApplyBind m a b) :: Type -> Type #

Methods

from :: ApplyBind m a b -> Rep (ApplyBind m a b) x #

to :: Rep (ApplyBind m a b) x -> ApplyBind m a b #

Monad m => Applicable (ApplyBind m a b) (m a) (m b) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ApplyBind m a b -> m a -> m b Source #

type Rep (ApplyBind m a b) Source # 
Instance details

Defined in Data.Applicable

type Rep (ApplyBind m a b) = D1 ('MetaData "ApplyBind" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "AppBind" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAppBind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> m b))))

newtype GroupAction a Source #

A wrapper for Semigroup members, representing the associated group action. Can be applied to another member, (<>)-ing them.

Constructors

GrpAct 

Fields

Instances

Instances details
Foldable GroupAction Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

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

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

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

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

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

toList :: GroupAction a -> [a] #

null :: GroupAction a -> Bool #

length :: GroupAction a -> Int #

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

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

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

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

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

Traversable GroupAction Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

Functor GroupAction Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

Data a => Data (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

toConstr :: GroupAction a -> Constr #

dataTypeOf :: GroupAction a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (GroupAction a) :: Type -> Type #

Methods

from :: GroupAction a -> Rep (GroupAction a) x #

to :: Rep (GroupAction a) x -> GroupAction a #

Ix a => Ix (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Read a => Read (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Show a => Show (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Eq a => Eq (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Ord a => Ord (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

Semigroup a => Applicable (GroupAction a) a a Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: GroupAction a -> a -> a Source #

type Rep (GroupAction a) Source # 
Instance details

Defined in Data.Applicable

type Rep (GroupAction a) = D1 ('MetaData "GroupAction" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "GrpAct" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGrpAct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype ChurchBool Source #

A wrapper for Bools. When applied to a value, uses the Church encoding of Booleans. The Church encoding of Booleans is a binary function that returns its first argument for True, and its second for False.

Constructors

ChBool 

Fields

Instances

Instances details
Data ChurchBool Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

toConstr :: ChurchBool -> Constr #

dataTypeOf :: ChurchBool -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ChurchBool Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep ChurchBool :: Type -> Type #

Ix ChurchBool Source # 
Instance details

Defined in Data.Applicable

Read ChurchBool Source # 
Instance details

Defined in Data.Applicable

Show ChurchBool Source # 
Instance details

Defined in Data.Applicable

Eq ChurchBool Source # 
Instance details

Defined in Data.Applicable

Ord ChurchBool Source # 
Instance details

Defined in Data.Applicable

Applicable ChurchBool a (a -> a) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchBool -> a -> a -> a Source #

type Rep ChurchBool Source # 
Instance details

Defined in Data.Applicable

type Rep ChurchBool = D1 ('MetaData "ChurchBool" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "ChBool" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChBool") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype ChurchNumeral a Source #

A wrapper for natural numbers (approximated by Integral). When applied to a value, uses the Church encoding of natural numbers. Church numerals represent the number _n_ as a function that take another function and repeatedly applies it _n_ times.

Constructors

ChNum 

Fields

Instances

Instances details
Foldable ChurchNumeral Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

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

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

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

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

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

toList :: ChurchNumeral a -> [a] #

null :: ChurchNumeral a -> Bool #

length :: ChurchNumeral a -> Int #

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

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

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

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

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

Traversable ChurchNumeral Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

Functor ChurchNumeral Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

Data a => Data (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

toConstr :: ChurchNumeral a -> Constr #

dataTypeOf :: ChurchNumeral a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ChurchNumeral a) :: Type -> Type #

Ix a => Ix (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Read a => Read (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Show a => Show (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Eq a => Eq (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Ord a => Ord (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

Integral a => Applicable (ChurchNumeral a) (a -> a) (a -> a) Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchNumeral a -> (a -> a) -> a -> a Source #

type Rep (ChurchNumeral a) Source # 
Instance details

Defined in Data.Applicable

type Rep (ChurchNumeral a) = D1 ('MetaData "ChurchNumeral" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "ChNum" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype ChurchTuple a b Source #

A wrapper for tuples (,). When applied to a value, uses the Church encoding of tuples. The Church encoding of tuples applies a function to the values inside a tuple.

Constructors

ChTup 

Fields

Instances

Instances details
Bifunctor ChurchTuple Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

Foldable (ChurchTuple a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

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

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

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

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

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

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

null :: ChurchTuple a a0 -> Bool #

length :: ChurchTuple a a0 -> Int #

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

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

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

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

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

Traversable (ChurchTuple a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

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

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

Functor (ChurchTuple a) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

(Data a, Data b) => Data (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

toConstr :: ChurchTuple a b -> Constr #

dataTypeOf :: ChurchTuple a b -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

Associated Types

type Rep (ChurchTuple a b) :: Type -> Type #

Methods

from :: ChurchTuple a b -> Rep (ChurchTuple a b) x #

to :: Rep (ChurchTuple a b) x -> ChurchTuple a b #

(Ix a, Ix b) => Ix (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

(Read a, Read b) => Read (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

(Show a, Show b) => Show (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

Methods

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

show :: ChurchTuple a b -> String #

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

(Eq a, Eq b) => Eq (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

Methods

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

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

(Ord a, Ord b) => Ord (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

Methods

compare :: ChurchTuple a b -> ChurchTuple a b -> Ordering #

(<) :: ChurchTuple a b -> ChurchTuple a b -> Bool #

(<=) :: ChurchTuple a b -> ChurchTuple a b -> Bool #

(>) :: ChurchTuple a b -> ChurchTuple a b -> Bool #

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

max :: ChurchTuple a b -> ChurchTuple a b -> ChurchTuple a b #

min :: ChurchTuple a b -> ChurchTuple a b -> ChurchTuple a b #

Applicable (ChurchTuple a b) (a -> b -> c) c Source # 
Instance details

Defined in Data.Applicable

Methods

($*) :: ChurchTuple a b -> (a -> b -> c) -> c Source #

type Rep (ChurchTuple a b) Source # 
Instance details

Defined in Data.Applicable

type Rep (ChurchTuple a b) = D1 ('MetaData "ChurchTuple" "Data.Applicable" "applicable-0.4.1.0-inplace" 'True) (C1 ('MetaCons "ChTup" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChTup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, b))))