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

Optics.Internal.Optic.TypeLevel

Description

This module is intended for internal use only, and may change without warning in subsequent releases.

Synopsis

Documentation

type IxList = [Type] Source #

A list of index types, used for indexed optics.

Since: 0.2

type NoIx = '[] :: IxList Source #

An alias for an empty index-list

type WithIx i = '[i] :: IxList Source #

Singleton index list

type family ShowSymbolWithOrigin symbol origin :: ErrorMessage where ... Source #

Equations

ShowSymbolWithOrigin symbol origin = ((('Text " " :<>: QuoteSymbol symbol) :<>: 'Text " (from ") :<>: 'Text origin) :<>: 'Text ")" 

type family ShowSymbolsWithOrigin (fs :: [(Symbol, Symbol)]) :: ErrorMessage where ... Source #

Equations

ShowSymbolsWithOrigin '['(symbol, origin)] = ShowSymbolWithOrigin symbol origin 
ShowSymbolsWithOrigin ('(symbol, origin) ': rest) = ShowSymbolWithOrigin symbol origin :$$: ShowSymbolsWithOrigin rest 

type family ShowOperators (ops :: [Symbol]) :: ErrorMessage where ... Source #

Equations

ShowOperators '[op] = QuoteSymbol op :<>: 'Text " (from Optics.Operators)" 
ShowOperators (op ': rest) = (QuoteSymbol op :<>: 'Text " ") :<>: ShowOperators rest 

type family AppendEliminations a b where ... Source #

Equations

AppendEliminations '(fs1, ops1) '(fs2, ops2) = '(Append fs1 fs2, Append ops1 ops2) 

type family ShowEliminations forms :: ErrorMessage where ... Source #

Equations

ShowEliminations '(fs, ops) = ShowSymbolsWithOrigin fs :$$: ('Text " " :<>: ShowOperators ops) 

type family Reverse (xs :: [k]) (acc :: [k]) :: [k] where ... Source #

Reverse a type-level list.

Equations

Reverse '[] acc = acc 
Reverse (x ': xs) acc = Reverse xs (x ': acc) 

type family Curry (xs :: IxList) (y :: Type) :: Type where ... Source #

Curry a type-level list.

In pseudo (dependent-)Haskell:

Curry xs y = foldr (->) y xs

Equations

Curry '[] y = y 
Curry (x ': xs) y = x -> Curry xs y 

type family Append (xs :: [k]) (ys :: [k]) :: [k] where ... Source #

Append two type-level lists together.

Equations

Append '[] ys = ys 
Append xs '[] = xs 
Append (x ': xs) ys = x ': Append xs ys 

class CurryCompose xs where Source #

Class that is inhabited by all type-level lists xs, providing the ability to compose a function under Curry xs.

Methods

composeN :: (i -> j) -> Curry xs i -> Curry xs j Source #

Compose a function under Curry xs. This generalises (.) (aka fmap for (->)) to work for curried functions with one argument for each type in the list.

Instances

Instances details
CurryCompose ('[] :: [Type]) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry '[] i -> Curry '[] j Source #

CurryCompose xs => CurryCompose (x ': xs) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry (x ': xs) i -> Curry (x ': xs) j Source #

data IxEq i is js where Source #

Tagged version of 'Data.Type.Equality.(:~:)' for carrying evidence that two index lists in a curried form are equal.

Constructors

IxEq :: IxEq i is is 

class AppendIndices xs ys ks | xs ys -> ks where Source #

In pseudo (dependent-)Haskell, provide a witness

foldr f (foldr f init xs) ys = foldr f init (ys ++ xs)
   where f = (->)

Since: 0.4

Methods

appendIndices :: IxEq i (Curry xs (Curry ys i)) (Curry ks i) Source #

Instances

Instances details
AppendIndices xs ('[] :: [Type]) xs Source #

If the second list is empty, we can shortcircuit and pick the first list immediately.

Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry xs (Curry '[] i)) (Curry xs i) Source #

AppendIndices ('[] :: [Type]) ys ys Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry '[] (Curry ys i)) (Curry ys i) Source #

AppendIndices xs ys ks => AppendIndices (x ': xs) ys (x ': ks) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry (x ': xs) (Curry ys i)) (Curry (x ': ks) i) Source #

type family FirstRight (m1 :: Either e a) (m2 :: Either e a) :: Either e a where ... Source #

If lhs is Right, return it. Otherwise check rhs.

Equations

FirstRight ('Right a) _ = 'Right a 
FirstRight _ b = b 

type family FromRight (def :: b) (e :: Either a b) :: b where ... Source #

Equations

FromRight _ ('Right b) = b 
FromRight def ('Left _) = def 

type family IsLeft (e :: Either a b) :: Bool where ... Source #

Equations

IsLeft ('Left _) = 'True 
IsLeft ('Right _) = 'False 

type family When (p :: Bool) (err :: Constraint) :: Constraint where ... Source #

Show a custom type error if p is true.

Equations

When 'True err = err 
When 'False _ = () 

type family Unless (p :: Bool) (err :: Constraint) :: Constraint where ... Source #

Show a custom type error if p is false (or stuck).

Equations

Unless 'True _ = () 
Unless 'False err = err 

type family Defined (f :: k) :: Bool where ... Source #

Use with Unless to detect stuck (undefined) type families.

Equations

Defined (f _) = Defined f 
Defined _ = 'True 

type family QuoteType (x :: t) :: ErrorMessage where ... Source #

Show a type surrounded by quote marks.

Equations

QuoteType x = ('Text "\8216" :<>: 'ShowType x) :<>: 'Text "\8217" 

type family QuoteSymbol (x :: Symbol) :: ErrorMessage where ... Source #

Show a symbol surrounded by quote marks.

Equations

QuoteSymbol x = ('Text "\8216" :<>: 'Text x) :<>: 'Text "\8217" 

type family ToOrdinal (n :: Nat) :: ErrorMessage where ... Source #

Equations

ToOrdinal 1 = 'Text "1st" 
ToOrdinal 2 = 'Text "2nd" 
ToOrdinal 3 = 'Text "3rd" 
ToOrdinal n = 'ShowType n :<>: 'Text "th" 

class HasShapeOf (a :: k) (b :: k) Source #

Derive the shape of a from the shape of b.

Instances

Instances details
a ~ b => HasShapeOf (a :: k) (b :: k) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

(fa ~ f a, HasShapeOf f g) => HasShapeOf (fa :: k1) (g b :: k1) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel