Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal implementation details of indexed optics.
This module is intended for internal use only, and may change without warning in subsequent releases.
Synopsis
- class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: IxList)
- class NonEmptyIndices (is :: IxList)
- class is ~ '[i] => HasSingleIndex (is :: IxList) (i :: Type)
- type family ShowTypes (types :: [Type]) :: ErrorMessage where ...
- data IntT f a = IntT !Int (f a)
- unIntT :: IntT f a -> f a
- newtype Indexing f a = Indexing {
- runIndexing :: Int -> IntT f a
- indexing :: ((a -> Indexing f b) -> s -> Indexing f t) -> (Int -> a -> f b) -> s -> f t
- conjoined :: is `HasSingleIndex` i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b
Documentation
class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: IxList) Source #
Show useful error message when a function expects optics without indices.
Instances
AcceptsEmptyIndices f ([] :: [Type]) Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError ((Text "\8216" :<>: Text f) :<>: Text "\8217 accepts only optics with no indices") :: Constraint), (x ': xs) ~ NoIx) => AcceptsEmptyIndices f (x ': xs) Source # | |
Defined in Optics.Internal.Indexed |
class NonEmptyIndices (is :: IxList) Source #
Check whether a list of indices is not empty and generate sensible error message if it's not.
Instances
(TypeError (Text "Indexed optic is expected") :: Constraint) => NonEmptyIndices ([] :: [Type]) Source # | |
Defined in Optics.Internal.Indexed | |
NonEmptyIndices (x ': xs) Source # | |
Defined in Optics.Internal.Indexed |
class is ~ '[i] => HasSingleIndex (is :: IxList) (i :: Type) Source #
Generate sensible error messages in case a user tries to pass either an unindexed optic or indexed optic with unflattened indices where indexed optic with a single index is expected.
Instances
((TypeError (Text "Indexed optic is expected") :: Constraint), ([] :: [Type]) ~ (i ': ([] :: [Type]))) => HasSingleIndex ([] :: [Type]) i Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icomposeN to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))) i Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose5 to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) i Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose4 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) i Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose3 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': ([] :: [Type])))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': ([] :: [Type])))) i Source # | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use (<%>) or icompose to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': ([] :: [Type]))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': ([] :: [Type]))) i Source # | |
Defined in Optics.Internal.Indexed | |
HasSingleIndex (i ': ([] :: [Type])) i Source # | |
Defined in Optics.Internal.Indexed |
type family ShowTypes (types :: [Type]) :: ErrorMessage where ... Source #
Indexing | |
|
Instances
Functor f => Functor (Indexing f) Source # | |
Applicative f => Applicative (Indexing f) Source # | |
Defined in Optics.Internal.Indexed |
indexing :: ((a -> Indexing f b) -> s -> Indexing f t) -> (Int -> a -> f b) -> s -> f t Source #
Index a traversal by position of visited elements.