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

Pandora.Paradigm.Primary.Functor.Conclusion

Documentation

data Conclusion e a Source #

Constructors

Failure e 
Success a 

Instances

Instances details
Bivariant Conclusion ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(<->) :: (a -> b) -> (c -> d) -> Conclusion a c -> Conclusion b d Source #

Monad (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Interpreted (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Associated Types

type Primary (Conclusion e) a Source #

Methods

run :: Conclusion e a -> Primary (Conclusion e) a Source #

unite :: Primary (Conclusion e) a -> Conclusion e a Source #

(||=) :: Interpreted u => (Primary (Conclusion e) a -> Primary u b) -> Conclusion e a -> u b Source #

(=||) :: Interpreted u => (Conclusion e a -> u b) -> Primary (Conclusion e) a -> Primary u b Source #

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

(<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Primary (Conclusion e) a -> Primary u b) -> ((j :. k) := Conclusion e a) -> (j :. k) := u b Source #

(<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Primary (Conclusion e) a -> Primary u b) -> ((j :. (k :. l)) := Conclusion e a) -> (j :. (k :. l)) := u b Source #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Primary (Conclusion e) a -> Primary u b) -> ((j :. (k :. (l :. m))) := Conclusion e a) -> (j :. (k :. (l :. m))) := u b Source #

(=||$>) :: (Covariant j (->) (->), Interpreted u) => (Conclusion e a -> u b) -> (j := Primary (Conclusion e) a) -> j := Primary u b Source #

(=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Conclusion e a -> u b) -> ((j :. k) := Primary (Conclusion e) a) -> (j :. k) := Primary u b Source #

(=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Conclusion e a -> u b) -> ((j :. (k :. l)) := Primary (Conclusion e) a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Conclusion e a -> u b) -> ((j :. (k :. (l :. m))) := Primary (Conclusion e) a) -> (j :. (k :. (l :. m))) := Primary u b Source #

Monadic (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

wrap :: forall (u :: Type -> Type). Pointable u (->) => Conclusion e ~> (Conclusion e :> u) Source #

Catchable e (Conclusion e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

catch :: forall (a :: k). Conclusion e a -> (e -> Conclusion e a) -> Conclusion e a Source #

(Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a Source #

Semigroup e => Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:+:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

multiply_ :: forall (a :: k) (b :: k). (Conclusion e a :*: Conclusion e b) -> Conclusion e (a :+: b) Source #

Semimonoidal (Conclusion e :: Type -> Type) ((->) :: Type -> Type -> Type) (:*:) (:*:) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

multiply_ :: forall (a :: k) (b :: k). (Conclusion e a :*: Conclusion e b) -> Conclusion e (a :*: b) Source #

Pointable (Conclusion e) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

point :: a -> Conclusion e a Source #

Bindable (Conclusion e) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(=<<) :: (a -> Conclusion e b) -> Conclusion e a -> Conclusion e b Source #

Morphable ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into (Flip Conclusion e)) Maybe :: Type -> Type Source #

Morphable ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into (Conclusion e)) Maybe :: Type -> Type Source #

Morphable ('Into Maybe) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

Associated Types

type Morphing ('Into Maybe) (Conclusion e) :: Type -> Type Source #

Covariant (Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(-<$>-) :: (a -> b) -> Conclusion e a -> Conclusion e b Source #

Traversable (Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(<<-) :: (Covariant u (->) (->), Pointable u (->), Semimonoidal u (->) (:*:) (:*:)) => (a -> u b) -> Conclusion e a -> u (Conclusion e b) Source #

(Semigroup e, Semigroup a) => Semigroup (Conclusion e a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(+) :: Conclusion e a -> Conclusion e a -> Conclusion e a Source #

(Setoid e, Setoid a) => Setoid (Conclusion e a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(==) :: Conclusion e a -> Conclusion e a -> Boolean Source #

(!=) :: Conclusion e a -> Conclusion e a -> Boolean Source #

(Chain e, Chain a) => Chain (Conclusion e a) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Covariant (Flip Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

(-<$>-) :: (a -> b) -> Flip Conclusion e a -> Flip Conclusion e b Source #

type Schematic Monad (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

type Primary (Conclusion e) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

type Primary (Conclusion e) a = Conclusion e a
type Morphing ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe = ((->) e :: Type -> Type) <:.> Flip Conclusion e
type Morphing ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary

type Morphing ('Into (Conclusion e) :: Morph (Type -> Type)) Maybe = ((->) e :: Type -> Type) <:.> Conclusion e
type Morphing ('Into Maybe) (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary

conclusion :: (e -> r) -> (a -> r) -> Conclusion e a -> r Source #

fail :: (e -> r) -> Conclusion e ~> Conclusion r Source #

failure :: Failable e t => e -> t a Source #

class Catchable e t where Source #

Methods

catch :: t a -> (e -> t a) -> t a Source #

Instances

Instances details
Catchable e (Conclusion e :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

catch :: forall (a :: k). Conclusion e a -> (e -> Conclusion e a) -> Conclusion e a Source #

(Pointable u ((->) :: Type -> Type -> Type), Bindable u ((->) :: Type -> Type -> Type)) => Catchable e (Conclusion e <.:> u :: Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Methods

catch :: forall (a :: k). (Conclusion e <.:> u) a -> (e -> (Conclusion e <.:> u) a) -> (Conclusion e <.:> u) a Source #