Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pandora.Paradigm.Primary.Transformer.Flip
Documentation
newtype Flip (v :: * -> * -> *) a e Source #
Constructors
Flip (v e a) |
Instances
Semigroupoid (Flip ((->) :: Type -> Type -> Type)) Source # | |
Category (Flip ((->) :: Type -> Type -> Type)) Source # | |
Morphable ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe Source # | |
Morphable ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # | |
Morphable ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) Source # | |
Invariant (Flip Store r) Source # | |
Invariant (Flip (Lens available) tgt) Source # | |
Invariant (Flip State r) Source # | |
Interpreted (Flip v a) Source # | |
Defined in Pandora.Paradigm.Primary.Transformer Methods run :: Flip v a a0 -> Primary (Flip v a) a0 Source # unite :: Primary (Flip v a) a0 -> Flip v a a0 Source # (||=) :: Interpreted u => (Primary (Flip v a) a0 -> Primary u b) -> Flip v a a0 -> u b Source # (=||) :: Interpreted u => (Flip v a a0 -> u b) -> Primary (Flip v a) a0 -> Primary u b Source # (<$||=) :: (Covariant j (->) (->), Interpreted u) => (Primary (Flip v a) a0 -> Primary u b) -> (j := Flip v a a0) -> j := u b Source # (<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Primary (Flip v a) a0 -> Primary u b) -> ((j :. k) := Flip v a a0) -> (j :. k) := u b Source # (<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Primary (Flip v a) a0 -> Primary u b) -> ((j :. (k :. l)) := Flip v a a0) -> (j :. (k :. l)) := u b Source # (<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Primary (Flip v a) a0 -> Primary u b) -> ((j :. (k :. (l :. m))) := Flip v a a0) -> (j :. (k :. (l :. m))) := u b Source # (=||$>) :: (Covariant j (->) (->), Interpreted u) => (Flip v a a0 -> u b) -> (j := Primary (Flip v a) a0) -> j := Primary u b Source # (=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Flip v a a0 -> u b) -> ((j :. k) := Primary (Flip v a) a0) -> (j :. k) := Primary u b Source # (=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Flip v a a0 -> u b) -> ((j :. (k :. l)) := Primary (Flip v a) a0) -> (j :. (k :. l)) := Primary u b Source # (=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Flip v a a0 -> u b) -> ((j :. (k :. (l :. m))) := Primary (Flip v a) a0) -> (j :. (k :. (l :. m))) := Primary u b Source # | |
Substructure ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |
Extractable (Flip (:*:) a) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (Constant :: Type -> Type -> Type) b) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (:+:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (:*:) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip (Tagged :: Type -> Type -> Type) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Covariant (Flip Validation a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Validation Methods (-<$>-) :: (a0 -> b) -> Flip Validation a a0 -> Flip Validation a b Source # | |
Covariant (Flip Conclusion e) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Primary.Functor.Conclusion Methods (-<$>-) :: (a -> b) -> Flip Conclusion e a -> Flip Conclusion e b Source # | |
Contravariant (Flip ((->) :: Type -> Type -> Type) a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Contravariant (Flip Imprint a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Contravariant (Flip Environment a) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
Defined in Pandora.Paradigm.Inventory.Environment Methods (->$<-) :: (a0 -> b) -> Flip Environment a b -> Flip Environment a a0 Source # | |
Adjoint (Flip (:*:) s) ((->) s :: Type -> Type) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # | |
type Morphing ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe Source # | |
Defined in Pandora.Paradigm.Primary type Morphing ('Into (Flip Conclusion e) :: Morph (Type -> Type)) Maybe = ((->) e :: Type -> Type) <:.> Flip Conclusion e | |
type Morphing ('Into ('Here Maybe :: Wedge (Type -> Type) a1) :: Morph (Wedge (Type -> Type) a1)) (Flip Wedge a2) Source # | |
type Morphing ('Into ('That Maybe :: These (Type -> Type) a1) :: Morph (These (Type -> Type) a1)) (Flip These a2) Source # | |
type Primary (Flip v a) e Source # | |
Defined in Pandora.Paradigm.Primary.Transformer | |
type Available ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |
type Substance ('Left :: a1 -> Wye a1) (Flip (:*:) a2) Source # | |