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

Pandora.Paradigm.Structure.Modification.Tape

Documentation

type Tape structure = Exactly <:*:> (Reverse structure <:*:> structure) Source #

Orphan instances

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Impliable (Tape t a :: Type) Source # 
Instance details

Associated Types

type Arguments (Tape t a) = (args :: Type) Source #

Methods

imply :: Arguments (Tape t a) Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Right :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Associated Types

type Substance ('All 'Right) (Tape t <::> Tape t) :: Type -> Type Source #

(Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t, Semimonoidal (-->) (:*:) (:*:) t) => Substructure ('All ('Left :: a -> Horizontal a) :: Occurrence (a -> Horizontal a)) (Tape t <::> Tape t) Source # 
Instance details

Associated Types

type Substance ('All 'Left) (Tape t <::> Tape t) :: 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

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

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) t => Substructure ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Associated Types

type Substance 'Down (Tape t <::> Tape t) :: Type -> Type Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Up :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Associated Types

type Substance 'Up (Tape t <::> Tape t) :: Type -> Type Source #