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

Pandora.Paradigm.Structure.Ability.Slidable

Documentation

class Slidable d (s :: * -> *) where Source #

Associated Types

type Sliding d s :: * -> * Source #

Methods

slide :: ((State < s e) :> Sliding d s) >>> () Source #

Instances

Instances details
Slidable ('Right ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) (Construction (Maybe <:*:> Maybe)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Sliding ('Right 'Zig) (Construction (Maybe <:*:> Maybe)) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Stack structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping structure)) => Slidable ('Right :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Sliding 'Right (Tape structure) :: Type -> Type Source #

Methods

slide :: ((State < Tape structure e) :> Sliding 'Right (Tape structure)) >>> () Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping structure), Stack structure) => Slidable ('Left :: a -> Horizontal a) (Tape structure) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

type Sliding 'Left (Tape structure) :: Type -> Type Source #

Methods

slide :: ((State < Tape structure e) :> Sliding 'Left (Tape structure)) >>> () Source #