pandora-0.5.5: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Paradigm.Primary.Functor.Predicate

Documentation

newtype Predicate a Source #

Constructors

Predicate (a -> Boolean) 

Instances

Instances details
Monoidal (-->) (<--) (:*:) (:*:) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Semimonoidal (-->) (:*:) (:+:) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

mult :: forall (a :: k) (b :: k). (Predicate a :*: Predicate b) --> Predicate (a :+: b) Source #

Semimonoidal (-->) (:*:) (:*:) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

mult :: forall (a :: k) (b :: k). (Predicate a :*: Predicate b) --> Predicate (a :*: b) Source #

Interpreted ((->) :: Type -> Type -> Type) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Associated Types

type Primary Predicate a Source #

Methods

run :: ((->) < Predicate a) < Primary Predicate a Source #

unite :: ((->) < Primary Predicate a) < Predicate a Source #

(<~~~~~~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~~~~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~~~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~~) :: ((->) < Predicate a) < Primary Predicate a Source #

(<~) :: ((->) < Predicate a) < Primary Predicate a Source #

(=#-) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Primary Predicate a) < Primary u b) -> ((->) < Predicate a) < u b Source #

(-#=) :: (Semigroupoid (->), Interpreted (->) u) => (((->) < Predicate a) < u b) -> ((->) < Primary Predicate a) < Primary u b Source #

(<$=#-) :: (Semigroupoid (->), Covariant (->) (->) j, Interpreted (->) u) => (((->) < Primary Predicate a) < Primary u b) -> (j > Predicate a) -> (j > u b) Source #

(-#=$>) :: (Covariant (->) (->) j, Interpreted (->) u) => (((->) < Predicate a) < u b) -> (j > Primary Predicate a) -> (j > Primary u b) Source #

Contravariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Predicate Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

Methods

(>-|-) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|--) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|---) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|----) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|-----) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|------) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|-------) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|--------) :: (a -> b) -> Predicate b -> Predicate a Source #

(>-|-|-) :: (Contravariant (->) (Betwixt (->) (->)) u, Contravariant (Betwixt (->) (->)) (->) Predicate) => (a -> b) -> Predicate (u a) -> Predicate (u b) Source #

type Primary Predicate a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Predicate

type Primary Predicate a = a -> Boolean