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

Pandora.Paradigm.Structure.Interface.Zipper

Documentation

class Zippable (structure :: * -> *) Source #

Associated Types

type Breadcrumbs structure :: * -> * Source #

Instances

Instances details
Zippable List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs List :: Type -> Type Source #

Zippable (Construction Exactly) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Breadcrumbs (Construction Exactly) :: Type -> Type Source #

Zippable (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs (Construction Maybe) :: Type -> Type Source #

Zippable (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Breadcrumbs (Construction List) :: Type -> Type Source #

Zippable (Comprehension Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Breadcrumbs (Comprehension Maybe) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

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

Methods

imply :: Arguments (Tape t a) Source #

Morphable ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Morph (Type -> Type)) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses))))))) (Construction List) :: Type -> Type Source #

Morphable ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Right) (Tape Stream) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Associated Types

type Morphing ('Rotate 'Left) (Tape Stream) :: Type -> Type Source #

Morphable ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into List) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Tape > Construction Maybe) :: Type -> Type Source #

Morphable ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Right) (Turnover < Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Rotate 'Left) (Turnover < Tape List) :: Type -> Type Source #

Morphable ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Morphing ('Rotate 'Up) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Right ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Right 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Left ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Left 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Down 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

Substructure ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

Associated Types

type Substance ('Up 'Forest) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Tape

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 -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

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

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Tape List) List :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Comprehension Maybe) (Tape List) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Tape List) (Construction Maybe) :: Type -> Type Source #

Morphable (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Associated Types

type Morphing ('Into > Construction Maybe) (Tape > Construction Maybe) :: Type -> Type Source #

Extendable ((->) :: Type -> Type -> Type) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

Methods

(<<=) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<==) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<===) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<====) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<=====) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<======) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<=======) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

(<<========) :: (Tape Stream a -> b) -> Tape Stream a -> Tape Stream b Source #

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Right :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Left :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

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

Covariant ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Substructure ('Root :: a -> Segment a) (Tagged (Zippable structure) <:.> (Exactly <:*:> t)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Interface.Zipper

Associated Types

type Substance 'Root (Tagged (Zippable structure) <:.> (Exactly <:*:> t)) :: Type -> Type Source #

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

Defined in Pandora.Paradigm.Structure.Modification.Tape

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

Defined in Pandora.Paradigm.Structure.Modification.Tape

Associated Types

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

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) t => Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<-------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<-----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<---) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

(<<--) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape t a -> u (Tape t b) Source #

Traversable ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

Methods

(<<-) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<-------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<------) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<-----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<----) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<---) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

(<<--) :: (Covariant (->) (->) u, Monoidal (Straight (->)) (Straight (->)) (:*:) (:*:) u) => (a -> u b) -> Tape List a -> u (Tape List b) Source #

type Arguments (Tape t a :: Type) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Arguments (Tape t a :: Type) = a -> t a -> t a -> Tape t a
type Morphing ('Into (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) :: Morph (Type -> Type)) (Construction List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Morphing ('Into List) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) = Tape Stream
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Stream

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape Stream) = Tape Stream
type Morphing ('Into List) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Right :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing ('Rotate ('Left :: a -> Wye a) :: Morph (a -> Wye a)) ((Turnover :: (Type -> Type) -> Type -> Type) < Tape List) = (Turnover :: (Type -> Type) -> Type -> Type) < Tape List
type Morphing ('Rotate ('Up :: a -> Vertical a) :: Morph (a -> Vertical a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Right ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Left ('Forest :: a -> Segment a) :: Wye (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Down ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('Up ('Forest :: a -> Segment a) :: Vertical (a -> Segment a)) (Tagged (Zippable structure) <:.> (Exactly <:*:> (Roses <:*:> (Reverse Roses <:*:> (Roses <:*:> (List <::> Tape Roses)))))) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.Rose

type Substance ('All ('Right :: a -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Right :: a -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) = Tape t <::> t
type Substance ('All ('Left :: a -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('All ('Left :: a -> Wye a) :: Occurrence (a -> Wye a)) (Tape t <::> Tape t) = Tape t <::> Reverse t
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) List = Maybe <::> Tape List
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Comprehension Maybe) (Tape List) = Comprehension Maybe
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Tape List) (Construction Maybe) = Tape List
type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Some.List

type Morphing (('Into :: (Type -> Type) -> Morph (Type -> Type)) > Construction Maybe) (Tape > Construction Maybe) = Construction Maybe
type Substance ('Right :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Right :: a -> Wye a) (Tape t) = t
type Substance ('Left :: a -> Wye a) (Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Left :: a -> Wye a) (Tape t) = Reverse t
type Substance ('Root :: a -> Segment a) (Tagged (Zippable structure) <:.> (Exactly <:*:> t)) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Interface.Zipper

type Substance ('Root :: a -> Segment a) (Tagged (Zippable structure) <:.> (Exactly <:*:> t)) = Exactly
type Substance ('Down :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Down :: a -> Vertical a) (Tape t <::> Tape t) = Reverse t <::> Tape t
type Substance ('Up :: a -> Vertical a) (Tape t <::> Tape t) Source # 
Instance details

Defined in Pandora.Paradigm.Structure.Modification.Tape

type Substance ('Up :: a -> Vertical a) (Tape t <::> Tape t) = t <::> Tape t

type Zipper (structure :: * -> *) = Tagged (Zippable structure) <:.> (Exactly <:*:> Breadcrumbs structure) Source #

type Breadcrumbed structure t = (Zippable structure, Breadcrumbs structure ~ t) Source #

type family Fastenable structure rs where ... Source #

Equations

Fastenable structure (r ::: rs) = ((Morphable < Rotate r) < structure, Fastenable structure rs) 
Fastenable structure r = (Morphable < Rotate r) < structure 

Orphan instances

Semimonoidal (<--) (:*:) (:*:) t => Monoidal (<--) (-->) (:*:) (:*:) (Exactly <:*:> t) Source # 
Instance details

Methods

unit :: Proxy (:*:) -> (Unit (:*:) --> a) <-- (Exactly <:*:> t) a Source #

Semimonoidal (<--) (:*:) (:*:) t => Semimonoidal (<--) (:*:) (:*:) (Exactly <:*:> t :: Type -> Type) Source # 
Instance details

Methods

mult :: forall (a :: k) (b :: k). ((Exactly <:*:> t) a :*: (Exactly <:*:> t) b) <-- (Exactly <:*:> t) (a :*: b) Source #