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

Pandora.Paradigm.Controlflow.Effect.Interpreted

Documentation

type family Schematic (c :: (* -> *) -> k) (t :: * -> *) = (r :: (* -> *) -> * -> *) | r -> t Source #

Instances

Instances details
type Schematic Monad Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

type Schematic Comonad (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

type Schematic Comonad (Store s) = (:*:) s <:<.>:> ((->) s :: Type -> Type)
type Schematic Comonad (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

type Schematic Comonad (Imprint e) = (<.:>) ((->) e :: Type -> Type)
type Schematic Comonad (Equipment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

type Schematic Monad (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

type Schematic Monad (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

type Schematic Monad (State s) = ((->) s :: Type -> Type) <:<.>:> (:*:) s
type Schematic Monad (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

type Schematic Monad (Environment e) = (<:.>) ((->) e :: Type -> Type)
type Schematic Monad (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

class Interpreted t where Source #

Associated Types

type Primary t a :: * Source #

Methods

run :: t a -> Primary t a Source #

unite :: Primary t a -> t a Source #

Instances

Instances details
Interpreted Maybe Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Maybe

Associated Types

type Primary Maybe a Source #

(Extractable t, Pointable t, Applicative t) => Interpreted (Outline t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Outline

Associated Types

type Primary (Outline t) a Source #

Methods

run :: Outline t a -> Primary (Outline t) a Source #

unite :: Primary (Outline t) a -> Outline t a Source #

Interpreted (Comprehension t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Ability.Comprehension

Associated Types

type Primary (Comprehension t) a Source #

Interpreted (Conclusion e) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Functor.Conclusion

Associated Types

type Primary (Conclusion e) a Source #

Interpreted (Store s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Store

Associated Types

type Primary (Store s) a Source #

Methods

run :: Store s a -> Primary (Store s) a Source #

unite :: Primary (Store s) a -> Store s a Source #

Interpreted (State s) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.State

Associated Types

type Primary (State s) a Source #

Methods

run :: State s a -> Primary (State s) a Source #

unite :: Primary (State s) a -> State s a Source #

Interpreted (Imprint e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Imprint

Associated Types

type Primary (Imprint e) a Source #

Methods

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

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

Interpreted (Equipment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Equipment

Associated Types

type Primary (Equipment e) a Source #

Methods

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

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

Interpreted (Environment e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Environment

Associated Types

type Primary (Environment e) a Source #

Interpreted (Accumulator e) Source # 
Instance details

Defined in Pandora.Paradigm.Inventory.Accumulator

Associated Types

type Primary (Accumulator e) a Source #

Interpreted (Schematic Monad t u) => Interpreted (t :> u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Monadic

Associated Types

type Primary (t :> u) a Source #

Methods

run :: (t :> u) a -> Primary (t :> u) a Source #

unite :: Primary (t :> u) a -> (t :> u) a Source #

Interpreted (Backwards t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Backwards

Associated Types

type Primary (Backwards t) a Source #

Methods

run :: Backwards t a -> Primary (Backwards t) a Source #

unite :: Primary (Backwards t) a -> Backwards t a Source #

Interpreted (Reverse t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Reverse

Associated Types

type Primary (Reverse t) a Source #

Methods

run :: Reverse t a -> Primary (Reverse t) a Source #

unite :: Primary (Reverse t) a -> Reverse t a Source #

Interpreted (Schematic Comonad t u) => Interpreted (t :< u) Source # 
Instance details

Defined in Pandora.Paradigm.Controlflow.Effect.Transformer.Comonadic

Associated Types

type Primary (t :< u) a Source #

Methods

run :: (t :< u) a -> Primary (t :< u) a Source #

unite :: Primary (t :< u) a -> (t :< u) a Source #

Interpreted (T_ ct t) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_

Associated Types

type Primary (T_ ct t) a Source #

Methods

run :: T_ ct t a -> Primary (T_ ct t) a Source #

unite :: Primary (T_ ct t) a -> T_ ct t a Source #

Interpreted (Kan ('Left :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan 'Left t u b) a Source #

Methods

run :: Kan 'Left t u b a -> Primary (Kan 'Left t u b) a Source #

unite :: Primary (Kan 'Left t u b) a -> Kan 'Left t u b a Source #

Interpreted (Kan ('Right :: Type -> Wye Type) t u b) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Kan

Associated Types

type Primary (Kan 'Right t u b) a Source #

Methods

run :: Kan 'Right t u b a -> Primary (Kan 'Right t u b) a Source #

unite :: Primary (Kan 'Right t u b) a -> Kan 'Right t u b a Source #

Interpreted (U_T ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.U_T

Associated Types

type Primary (U_T ct cu t u) a Source #

Methods

run :: U_T ct cu t u a -> Primary (U_T ct cu t u) a Source #

unite :: Primary (U_T ct cu t u) a -> U_T ct cu t u a Source #

Interpreted (T_U ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.T_U

Associated Types

type Primary (T_U ct cu t u) a Source #

Methods

run :: T_U ct cu t u a -> Primary (T_U ct cu t u) a Source #

unite :: Primary (T_U ct cu t u) a -> T_U ct cu t u a Source #

Interpreted (UT ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UT

Associated Types

type Primary (UT ct cu t u) a Source #

Methods

run :: UT ct cu t u a -> Primary (UT ct cu t u) a Source #

unite :: Primary (UT ct cu t u) a -> UT ct cu t u a Source #

Interpreted (TU ct cu t u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TU

Associated Types

type Primary (TU ct cu t u) a Source #

Methods

run :: TU ct cu t u a -> Primary (TU ct cu t u) a Source #

unite :: Primary (TU ct cu t u) a -> TU ct cu t u a Source #

Interpreted (UTU ct cu t u u') Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.UTU

Associated Types

type Primary (UTU ct cu t u u') a Source #

Methods

run :: UTU ct cu t u u' a -> Primary (UTU ct cu t u u') a Source #

unite :: Primary (UTU ct cu t u u') a -> UTU ct cu t u u' a Source #

Interpreted (TUT ct ct' cu t t' u) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUT

Associated Types

type Primary (TUT ct ct' cu t t' u) a Source #

Methods

run :: TUT ct ct' cu t t' u a -> Primary (TUT ct ct' cu t t' u) a Source #

unite :: Primary (TUT ct ct' cu t t' u) a -> TUT ct ct' cu t t' u a Source #

Interpreted (TUVW ct cu cv cw t u v w) Source # 
Instance details

Defined in Pandora.Paradigm.Schemes.TUVW

Associated Types

type Primary (TUVW ct cu cv cw t u v w) a Source #

Methods

run :: TUVW ct cu cv cw t u v w a -> Primary (TUVW ct cu cv cw t u v w) a Source #

unite :: Primary (TUVW ct cu cv cw t u v w) a -> TUVW ct cu cv cw t u v w a Source #

(-=:) :: (Liftable t, Interpreted (t u), Interpreted (t v), Covariant u) => (t u a -> t v b) -> u a -> Primary (t v) b Source #