Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- generic :: (Generic a, Generic b) => Iso a b (Rep a x) (Rep b y)
- generic1 :: (Generic1 f, Generic1 g) => Iso (f x) (g y) (Rep1 f x) (Rep1 g y)
- _V1 :: Lens (V1 s) (V1 t) a b
- _U1 :: Iso (U1 p) (U1 q) () ()
- _Par1 :: Iso (Par1 p) (Par1 q) p q
- _Rec1 :: Iso (Rec1 f p) (Rec1 g q) (f p) (g q)
- _K1 :: Iso (K1 i c p) (K1 j d q) c d
- _M1 :: Iso (M1 i c f p) (M1 j d g q) (f p) (g q)
- _L1 :: Prism ((a :+: c) t) ((b :+: c) t) (a t) (b t)
- _R1 :: Prism ((c :+: a) t) ((c :+: b) t) (a t) (b t)
- class GFieldImpl (name :: Symbol) s t a b | name s -> a where
- gfieldImpl :: Lens s t a b
- class GSetFieldSum (path :: PathTree Symbol) g h b | path h -> b, path g b -> h where
- gsetFieldSum :: g x -> b -> h x
- class GSetFieldProd (path :: [Path]) g h b | path h -> b, path g b -> h where
- gsetFieldProd :: g x -> b -> h x
- class GAffineFieldImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where
- gafieldImpl :: AffineTraversal s t a b
- class GAffineFieldSum (path :: PathTree Symbol) g h a b where
- gafieldSum :: AffineTraversalVL (g x) (h x) a b
- class GFieldProd (path :: [Path]) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where
- gfieldProd :: LensVL (g x) (h x) a b
- class GPositionImpl (repDefined :: Bool) (n :: Nat) s t a b | n s -> a where
- gpositionImpl :: Lens s t a b
- class GPositionSum (path :: PathTree (Nat, Nat)) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where
- gpositionSum :: LensVL (g x) (h x) a b
- class GConstructorImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where
- gconstructorImpl :: Prism s t a b
- class GConstructorSum (path :: [Path]) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where
- gconstructorSum :: Prism (g x) (h x) a b
- class GConstructorTuple g h a b | g -> a, h -> b, g b -> h, h a -> g where
- gconstructorTuple :: Prism (g x) (h x) a b
- class GPlateImpl g a where
- gplateImpl :: TraversalVL' (g x) a
- class GPlateInner (repDefined :: Bool) s a where
- gplateInner :: TraversalVL' s a
- module Optics.Internal.Generic.TypeLevel
Documentation
generic :: (Generic a, Generic b) => Iso a b (Rep a x) (Rep b y) Source #
Convert from the data type to its representation (or back)
>>>
view (generic % re generic) "hello" :: String
"hello"
generic1 :: (Generic1 f, Generic1 g) => Iso (f x) (g y) (Rep1 f x) (Rep1 g y) Source #
Convert from the data type to its representation (or back)
Fields
class GFieldImpl (name :: Symbol) s t a b | name s -> a where Source #
gfieldImpl :: Lens s t a b Source #
Instances
(Generic s, Generic t, path ~ GetFieldPaths s name (Rep s), HasField name s a, GSetFieldSum path (Rep s) (Rep t) b) => GFieldImpl name s t a b Source # | |
Defined in Optics.Internal.Generic gfieldImpl :: Lens s t a b Source # |
class GSetFieldSum (path :: PathTree Symbol) g h b | path h -> b, path g b -> h where Source #
gsetFieldSum :: g x -> b -> h x Source #
Instances
GSetFieldSum path g h b => GSetFieldSum path (M1 D m g) (M1 D m h) b Source # | |
Defined in Optics.Internal.Generic | |
(path ~ GSetFieldPath con epath, When (IsLeft epath) (HideReps g h), GSetFieldProd path g h b) => GSetFieldSum ('PathLeaf epath) (M1 C ('MetaCons con fix hs) g) (M1 C ('MetaCons con fix hs) h) b Source # | |
Defined in Optics.Internal.Generic | |
(GSetFieldSum path1 g1 h1 b, GSetFieldSum path2 g2 h2 b) => GSetFieldSum ('PathTree path1 path2) (g1 :+: g2) (h1 :+: h2) b Source # | |
Defined in Optics.Internal.Generic gsetFieldSum :: (g1 :+: g2) x -> b -> (h1 :+: h2) x Source # |
class GSetFieldProd (path :: [Path]) g h b | path h -> b, path g b -> h where Source #
gsetFieldProd :: g x -> b -> h x Source #
Instances
r ~ b => GSetFieldProd ('[] :: [Path]) (M1 S m (Rec0 a)) (M1 S m (Rec0 b)) r Source # | |
Defined in Optics.Internal.Generic | |
(GSetFieldProd path g1 h1 b, g2 ~ h2) => GSetFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: h2) b Source # | |
Defined in Optics.Internal.Generic gsetFieldProd :: (g1 :*: g2) x -> b -> (h1 :*: h2) x Source # | |
GSetFieldProd path g1 h1 b => GSetFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: g2) b Source # | |
Defined in Optics.Internal.Generic gsetFieldProd :: (g1 :*: g2) x -> b -> (h1 :*: g2) x Source # | |
(GSetFieldProd path g2 h2 b, g1 ~ h1) => GSetFieldProd ('PathRight ': path) (g1 :*: g2) (h1 :*: h2) b Source # | |
Defined in Optics.Internal.Generic gsetFieldProd :: (g1 :*: g2) x -> b -> (h1 :*: h2) x Source # | |
GSetFieldProd path g2 h2 b => GSetFieldProd ('PathRight ': path) (g1 :*: g2) (g1 :*: h2) b Source # | |
Defined in Optics.Internal.Generic gsetFieldProd :: (g1 :*: g2) x -> b -> (g1 :*: h2) x Source # |
class GAffineFieldImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where Source #
gafieldImpl :: AffineTraversal s t a b Source #
Instances
(Generic s, Generic t, path ~ GetFieldPaths s name (Rep s), HasField name s a, Unless (AnyHasPath path) (TypeError ((('Text "Type " :<>: QuoteType s) :<>: 'Text " doesn't have a field named ") :<>: QuoteSymbol name) :: Constraint), GAffineFieldSum path (Rep s) (Rep t) a b) => GAffineFieldImpl 'True name s t a b Source # | |
Defined in Optics.Internal.Generic gafieldImpl :: AffineTraversal s t a b Source # |
class GAffineFieldSum (path :: PathTree Symbol) g h a b where Source #
gafieldSum :: AffineTraversalVL (g x) (h x) a b Source #
Instances
GAffineFieldSum path g h a b => GAffineFieldSum path (M1 D m g) (M1 D m h) a b Source # | |
Defined in Optics.Internal.Generic gafieldSum :: AffineTraversalVL (M1 D m g x) (M1 D m h x) a b Source # | |
GAffineFieldMaybe epath g h a b => GAffineFieldSum ('PathLeaf epath) (M1 C m g) (M1 C m h) a b Source # | |
Defined in Optics.Internal.Generic gafieldSum :: AffineTraversalVL (M1 C m g x) (M1 C m h x) a b Source # | |
(GAffineFieldSum path1 g1 h1 a b, GAffineFieldSum path2 g2 h2 a b) => GAffineFieldSum ('PathTree path1 path2) (g1 :+: g2) (h1 :+: h2) a b Source # | |
Defined in Optics.Internal.Generic gafieldSum :: AffineTraversalVL ((g1 :+: g2) x) ((h1 :+: h2) x) a b Source # |
class GFieldProd (path :: [Path]) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where Source #
gfieldProd :: LensVL (g x) (h x) a b Source #
Instances
(r ~ a, s ~ b) => GFieldProd ('[] :: [Path]) (M1 S m (Rec0 a)) (M1 S m (Rec0 b)) r s Source # | |
(GFieldProd path g1 h1 a b, g2 ~ h2) => GFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: h2) a b Source # | |
Defined in Optics.Internal.Generic | |
GFieldProd path g1 h1 a b => GFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: g2) a b Source # | |
Defined in Optics.Internal.Generic | |
(GFieldProd path g2 h2 a b, g1 ~ h1) => GFieldProd ('PathRight ': path) (g1 :*: g2) (h1 :*: h2) a b Source # | |
Defined in Optics.Internal.Generic | |
GFieldProd path g2 h2 a b => GFieldProd ('PathRight ': path) (g1 :*: g2) (g1 :*: h2) a b Source # | |
Defined in Optics.Internal.Generic |
Positions
class GPositionImpl (repDefined :: Bool) (n :: Nat) s t a b | n s -> a where Source #
gpositionImpl :: Lens s t a b Source #
Instances
(Generic s, Generic t, path ~ If (n <=? 0) (TypeError ('Text "There is no 0th position") :: PathTree (Nat, Nat)) (GetPositionPaths s n (Rep s)), When (n <=? 0) (HideReps (Rep s) (Rep t)), GPositionSum path (Rep s) (Rep t) a b) => GPositionImpl 'True n s t a b Source # | |
Defined in Optics.Internal.Generic gpositionImpl :: Lens s t a b Source # |
class GPositionSum (path :: PathTree (Nat, Nat)) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where Source #
gpositionSum :: LensVL (g x) (h x) a b Source #
Instances
GPositionSum path g h a b => GPositionSum path (M1 D m g) (M1 D m h) a b Source # | |
Defined in Optics.Internal.Generic | |
(path ~ GPositionPath con epath, When (IsLeft epath) (HideReps g h), GFieldProd path g h a b) => GPositionSum ('PathLeaf epath) (M1 C ('MetaCons con fix hs) g) (M1 C ('MetaCons con fix hs) h) a b Source # | |
(GPositionSum path1 g1 h1 a b, GPositionSum path2 g2 h2 a b) => GPositionSum ('PathTree path1 path2) (g1 :+: g2) (h1 :+: h2) a b Source # | |
Defined in Optics.Internal.Generic |
Constructors
class GConstructorImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where Source #
gconstructorImpl :: Prism s t a b Source #
Instances
(Generic s, Generic t, epath ~ GetNamePath name (Rep s) ('[] :: [Path]), path ~ FromRight (TypeError ((('Text "Type " :<>: QuoteType s) :<>: 'Text " doesn't have a constructor named ") :<>: QuoteSymbol name) :: [Path]) epath, When (IsLeft epath) (HideReps (Rep s) (Rep t)), GConstructorSum path (Rep s) (Rep t) a b) => GConstructorImpl 'True name s t a b Source # | |
Defined in Optics.Internal.Generic gconstructorImpl :: Prism s t a b Source # |
class GConstructorSum (path :: [Path]) g h a b | path g -> a, path h -> b, path g b -> h, path h a -> g where Source #
gconstructorSum :: Prism (g x) (h x) a b Source #
Instances
GConstructorSum path g h a b => GConstructorSum path (M1 D m g) (M1 D m h) a b Source # | |
Defined in Optics.Internal.Generic | |
GConstructorTuple g h a b => GConstructorSum ('[] :: [Path]) (M1 C m g) (M1 C m h) a b Source # | |
Defined in Optics.Internal.Generic | |
(GConstructorSum path g1 h1 a b, g2 ~ h2) => GConstructorSum ('PathLeft ': path) (g1 :+: g2) (h1 :+: h2) a b Source # | |
Defined in Optics.Internal.Generic | |
GConstructorSum path g1 h1 a b => GConstructorSum ('PathLeft ': path) (g1 :+: g2) (h1 :+: g2) a b Source # | |
Defined in Optics.Internal.Generic | |
(GConstructorSum path g2 h2 a b, g1 ~ h1) => GConstructorSum ('PathRight ': path) (g1 :+: g2) (h1 :+: h2) a b Source # | |
Defined in Optics.Internal.Generic | |
GConstructorSum path g2 h2 a b => GConstructorSum ('PathRight ': path) (g1 :+: g2) (g1 :+: h2) a b Source # | |
Defined in Optics.Internal.Generic |
class GConstructorTuple g h a b | g -> a, h -> b, g b -> h, h a -> g where Source #
gconstructorTuple :: Prism (g x) (h x) a b Source #
Instances
(Dysfunctional () () g h a b, TypeError (('Text "Generic based access supports constructors" :$$: 'Text "containing up to 5 fields. Please generate") :$$: 'Text "PrismS with Template Haskell if you need more.") :: Constraint) => GConstructorTuple g h a b Source # | |
Defined in Optics.Internal.Generic gconstructorTuple :: Prism (g x) (h x) a b Source # | |
(a ~ (), b ~ ()) => GConstructorTuple (U1 :: Type -> Type) (U1 :: Type -> Type) a b Source # | |
Defined in Optics.Internal.Generic |
Types
class GPlateImpl g a where Source #
gplateImpl :: TraversalVL' (g x) a Source #
Instances
class GPlateInner (repDefined :: Bool) s a where Source #
gplateInner :: TraversalVL' s a Source #
Instances
(Generic s, GPlateImpl (Rep s) a) => GPlateInner 'True s a Source # | |
Defined in Optics.Internal.Generic gplateInner :: TraversalVL' s a Source # | |
GPlateInner repNotDefined s a Source # | |
Defined in Optics.Internal.Generic gplateInner :: TraversalVL' s a Source # |