pandora-0.5.5: 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 #

Slidable ('Down ('Right :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Slidable ('Down ('Left :: a -> Horizontal a) :: Vertical (a -> Horizontal a)) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary

Slidable (('Right :: (a -> Splay a) -> Horizontal (a -> Splay a)) > ('Zig :: a -> Splay a) :: Horizontal (a -> Splay a)) Binary Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Splay

Associated Types

type Sliding ('Right > 'Zig) Binary :: Type -> Type Source #

Methods

slide :: ((State < Binary e) :> Sliding ('Right > 'Zig) Binary) >>> () Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Stack structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping 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 #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) structure, Bindable ((->) :: Type -> Type -> Type) (Topping structure), Monoidal (-->) (-->) (:*:) (:*:) (Topping structure), Stack 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 #

Slidable ('Down :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Down (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Right :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Right (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Left :: a -> Horizontal a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Left (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Up :: a -> Vertical a) (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Sliding 'Up (Exactly <:*:> (Roses <:*:> (List <::> Tape Roses))) :: Type -> Type Source #

Slidable ('Up :: a -> Vertical a) (Exactly <:*:> (((Maybe <:*:> Maybe) <::> Construction (Maybe <:*:> Maybe)) <:*:> (List <::> (Horizontal <::> (Exactly <:*:> Binary))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Binary