optics-core-0.4: Optics as an abstract interface: core definitions
Safe HaskellNone
LanguageHaskell2010

Optics.Internal.Generic

Synopsis

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)

_V1 :: Lens (V1 s) (V1 t) a b Source #

_U1 :: Iso (U1 p) (U1 q) () () Source #

_Par1 :: Iso (Par1 p) (Par1 q) p q Source #

_Rec1 :: Iso (Rec1 f p) (Rec1 g q) (f p) (g q) Source #

_K1 :: Iso (K1 i c p) (K1 j d q) c d Source #

_M1 :: Iso (M1 i c f p) (M1 j d g q) (f p) (g q) Source #

_L1 :: Prism ((a :+: c) t) ((b :+: c) t) (a t) (b t) Source #

_R1 :: Prism ((c :+: a) t) ((c :+: b) t) (a t) (b t) Source #

Fields

class GFieldImpl (name :: Symbol) s t a b | name s -> a where Source #

Methods

gfieldImpl :: Lens s t a b Source #

Instances

Instances details
(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldImpl :: Lens s t a b Source #

class GSetFieldSum (path :: PathTree Symbol) g h b | path h -> b, path g b -> h where Source #

Methods

gsetFieldSum :: g x -> b -> h x Source #

Instances

Instances details
GSetFieldSum path g h b => GSetFieldSum path (M1 D m g) (M1 D m h) b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldSum :: M1 D m g x -> b -> M1 D m h x Source #

(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldSum :: M1 C ('MetaCons con fix hs) g x -> b -> M1 C ('MetaCons con fix hs) h x Source #

(GSetFieldSum path1 g1 h1 b, GSetFieldSum path2 g2 h2 b) => GSetFieldSum ('PathTree path1 path2) (g1 :+: g2) (h1 :+: h2) b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 #

Methods

gsetFieldProd :: g x -> b -> h x Source #

Instances

Instances details
r ~ b => GSetFieldProd ('[] :: [Path]) (M1 S m (Rec0 a)) (M1 S m (Rec0 b)) r Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldProd :: M1 S m (Rec0 a) x -> r -> M1 S m (Rec0 b) x Source #

(GSetFieldProd path g1 h1 b, g2 ~ h2) => GSetFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: h2) b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldProd :: (g1 :*: g2) x -> b -> (h1 :*: h2) x Source #

GSetFieldProd path g1 h1 b => GSetFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: g2) b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldProd :: (g1 :*: g2) x -> b -> (h1 :*: h2) x Source #

GSetFieldProd path g2 h2 b => GSetFieldProd ('PathRight ': path) (g1 :*: g2) (g1 :*: h2) b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gsetFieldProd :: (g1 :*: g2) x -> b -> (g1 :*: h2) x Source #

class GAffineFieldImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where Source #

Instances

Instances details
(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 # 
Instance details

Defined in Optics.Internal.Generic

class GAffineFieldSum (path :: PathTree Symbol) g h a b where Source #

Methods

gafieldSum :: AffineTraversalVL (g x) (h x) a b Source #

Instances

Instances details
GAffineFieldSum path g h a b => GAffineFieldSum path (M1 D m g) (M1 D m h) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 #

Methods

gfieldProd :: LensVL (g x) (h x) a b Source #

Instances

Instances details
(r ~ a, s ~ b) => GFieldProd ('[] :: [Path]) (M1 S m (Rec0 a)) (M1 S m (Rec0 b)) r s Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldProd :: LensVL (M1 S m (Rec0 a) x) (M1 S m (Rec0 b) x) r s Source #

(GFieldProd path g1 h1 a b, g2 ~ h2) => GFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldProd :: LensVL ((g1 :*: g2) x) ((h1 :*: h2) x) a b Source #

GFieldProd path g1 h1 a b => GFieldProd ('PathLeft ': path) (g1 :*: g2) (h1 :*: g2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldProd :: LensVL ((g1 :*: g2) x) ((h1 :*: g2) x) a b Source #

(GFieldProd path g2 h2 a b, g1 ~ h1) => GFieldProd ('PathRight ': path) (g1 :*: g2) (h1 :*: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldProd :: LensVL ((g1 :*: g2) x) ((h1 :*: h2) x) a b Source #

GFieldProd path g2 h2 a b => GFieldProd ('PathRight ': path) (g1 :*: g2) (g1 :*: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gfieldProd :: LensVL ((g1 :*: g2) x) ((g1 :*: h2) x) a b Source #

Positions

class GPositionImpl (repDefined :: Bool) (n :: Nat) s t a b | n s -> a where Source #

Methods

gpositionImpl :: Lens s t a b Source #

Instances

Instances details
(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 #

Methods

gpositionSum :: LensVL (g x) (h x) a b Source #

Instances

Instances details
GPositionSum path g h a b => GPositionSum path (M1 D m g) (M1 D m h) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gpositionSum :: LensVL (M1 D m g x) (M1 D m h x) a b Source #

(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gpositionSum :: LensVL (M1 C ('MetaCons con fix hs) g x) (M1 C ('MetaCons con fix hs) h x) 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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gpositionSum :: LensVL ((g1 :+: g2) x) ((h1 :+: h2) x) a b Source #

Constructors

class GConstructorImpl (repDefined :: Bool) (name :: Symbol) s t a b | name s -> a where Source #

Methods

gconstructorImpl :: Prism s t a b Source #

Instances

Instances details
(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

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 #

Methods

gconstructorSum :: Prism (g x) (h x) a b Source #

Instances

Instances details
GConstructorSum path g h a b => GConstructorSum path (M1 D m g) (M1 D m h) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism (M1 D m g x) (M1 D m h x) a b Source #

GConstructorTuple g h a b => GConstructorSum ('[] :: [Path]) (M1 C m g) (M1 C m h) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism (M1 C m g x) (M1 C m h x) a b Source #

(GConstructorSum path g1 h1 a b, g2 ~ h2) => GConstructorSum ('PathLeft ': path) (g1 :+: g2) (h1 :+: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism ((g1 :+: g2) x) ((h1 :+: h2) x) a b Source #

GConstructorSum path g1 h1 a b => GConstructorSum ('PathLeft ': path) (g1 :+: g2) (h1 :+: g2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism ((g1 :+: g2) x) ((h1 :+: g2) x) a b Source #

(GConstructorSum path g2 h2 a b, g1 ~ h1) => GConstructorSum ('PathRight ': path) (g1 :+: g2) (h1 :+: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism ((g1 :+: g2) x) ((h1 :+: h2) x) a b Source #

GConstructorSum path g2 h2 a b => GConstructorSum ('PathRight ': path) (g1 :+: g2) (g1 :+: h2) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorSum :: Prism ((g1 :+: g2) x) ((g1 :+: h2) x) a b Source #

class GConstructorTuple g h a b | g -> a, h -> b, g b -> h, h a -> g where Source #

Methods

gconstructorTuple :: Prism (g x) (h x) a b Source #

Instances

Instances details
(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 # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorTuple :: Prism (g x) (h x) a b Source #

(a ~ (), b ~ ()) => GConstructorTuple (U1 :: Type -> Type) (U1 :: Type -> Type) a b Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gconstructorTuple :: Prism (U1 x) (U1 x) a b Source #

Types

class GPlateImpl g a where Source #

Methods

gplateImpl :: TraversalVL' (g x) a Source #

Instances

Instances details
GPlateImpl (V1 :: Type -> Type) a Source # 
Instance details

Defined in Optics.Internal.Generic

GPlateImpl (U1 :: Type -> Type) a Source # 
Instance details

Defined in Optics.Internal.Generic

GPlateImpl (URec b :: Type -> Type) a Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' (URec b x) a Source #

GPlateInner (Defined (Rep b)) b a => GPlateImpl (K1 i b :: Type -> Type) a Source #

Recurse into the inner type if it has a Generic instance.

Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' (K1 i b x) a Source #

GPlateImpl (K1 i a :: Type -> Type) a Source #

Matching type.

Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' (K1 i a x) a Source #

(GPlateImpl f a, GPlateImpl g a) => GPlateImpl (f :+: g) a Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' ((f :+: g) x) a Source #

(GPlateImpl f a, GPlateImpl g a) => GPlateImpl (f :*: g) a Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' ((f :*: g) x) a Source #

GPlateImpl f a => GPlateImpl (M1 i c f) a Source # 
Instance details

Defined in Optics.Internal.Generic

Methods

gplateImpl :: TraversalVL' (M1 i c f x) a Source #

class GPlateInner (repDefined :: Bool) s a where Source #

Instances

Instances details
(Generic s, GPlateImpl (Rep s) a) => GPlateInner 'True s a Source # 
Instance details

Defined in Optics.Internal.Generic

GPlateInner repNotDefined s a Source # 
Instance details

Defined in Optics.Internal.Generic

Re-export