HList-0.5.3.0: Heterogeneous lists
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HList

Description

OOHaskell (C) 2004, Oleg Kiselyov, Ralf Laemmel, Keean Schupke

This module gathers the API that we need for OOP in Haskell. We basically select a certain configuration of the HList library, and we also import modules that are needed for mutable data and monads. Note on overlapping: Needed for the chosen model of labels. Other models can be used instead, but the chosen look better in types.

Synopsis

Documentation

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

>>> mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

(HProxies a, HMapCxt HList ConstMempty (AddProxy a) a, HZip HList a a aa, HMapCxt HList UncurryMappend aa a) => Monoid (HList a) Source #

Analogous to the Monoid instance for tuples

>>> import Data.Monoid
>>> mempty :: HList '[(), All, [Int]]
H[(),All {getAll = True},[]]
>>> mappend (hBuild "a") (hBuild "b") :: HList '[String]
H["ab"]
Instance details

Defined in Data.HList.HList

Methods

mempty :: HList a #

mappend :: HList a -> HList a -> HList a #

mconcat :: [HList a] -> HList a #

Monoid (HList r) => Monoid (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

mempty :: Record r #

mappend :: Record r -> Record r -> Record r #

mconcat :: [Record r] -> Record r #

Monoid (Variant l) => Monoid (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

mempty :: TIC l #

mappend :: TIC l -> TIC l -> TIC l #

mconcat :: [TIC l] -> TIC l #

Monoid (HList a) => Monoid (TIP a) Source # 
Instance details

Defined in Data.HList.TIP

Methods

mempty :: TIP a #

mappend :: TIP a -> TIP a -> TIP a #

mconcat :: [TIP a] -> TIP a #

(Monoid x, Monoid (Variant (a ': b))) => Monoid (Variant (Tagged t x ': (a ': b))) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant (Tagged t x ': (a ': b)) #

mappend :: Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

mconcat :: [Variant (Tagged t x ': (a ': b))] -> Variant (Tagged t x ': (a ': b)) #

(Unvariant '[Tagged t x] x, Monoid x) => Monoid (Variant '[Tagged t x]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant '[Tagged t x] #

mappend :: Variant '[Tagged t x] -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

mconcat :: [Variant '[Tagged t x]] -> Variant '[Tagged t x] #

Monoid (Comparison a)

mempty on comparisons always returns EQ. Without newtypes this equals pure (pure EQ).

mempty :: Comparison a
mempty = Comparison _ _ -> EQ
Instance details

Defined in Data.Functor.Contravariant

Monoid (Equivalence a)

mempty on equivalences always returns True. Without newtypes this equals pure (pure True).

mempty :: Equivalence a
mempty = Equivalence _ _ -> True
Instance details

Defined in Data.Functor.Contravariant

Monoid (Predicate a)

mempty on predicates always returns True. Without newtypes this equals pure True.

mempty :: Predicate a
mempty = _ -> True
Instance details

Defined in Data.Functor.Contravariant

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

mconcat :: [Down a] -> Down a #

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Monoid (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

mconcat :: [Doc a] -> Doc a #

Monoid a => Monoid (Q a)

Since: template-haskell-2.17.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

mempty :: Q a #

mappend :: Q a -> Q a -> Q a #

mconcat :: [Q a] -> Q a #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

mempty :: (a) #

mappend :: (a) -> (a) -> (a) #

mconcat :: [(a)] -> (a) #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Op a b)

mempty @(Op a b) without newtypes is mempty @(b->a) = _ -> mempty.

mempty :: Op a b
mempty = Op _ -> mempty
Instance details

Defined in Data.Functor.Contravariant

Methods

mempty :: Op a b #

mappend :: Op a b -> Op a b -> Op a b #

mconcat :: [Op a b] -> Op a b #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

mappend :: ST s a -> ST s a -> ST s a #

mconcat :: [ST s a] -> ST s a #

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

(Profunctor p, Arrow p, Semigroup b, Monoid b) => Monoid (Closure p a b) 
Instance details

Defined in Data.Profunctor.Closed

Methods

mempty :: Closure p a b #

mappend :: Closure p a b -> Closure p a b -> Closure p a b #

mconcat :: [Closure p a b] -> Closure p a b #

ArrowPlus p => Monoid (Tambara p a b) 
Instance details

Defined in Data.Profunctor.Strong

Methods

mempty :: Tambara p a b #

mappend :: Tambara p a b -> Tambara p a b -> Tambara p a b #

mconcat :: [Tambara p a b] -> Tambara p a b #

(Semigroup a, Monoid a) => Monoid (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

mempty :: Tagged s a #

mappend :: Tagged s a -> Tagged s a -> Tagged s a #

mconcat :: [Tagged s a] -> Tagged s a #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty :: Product f g a #

mappend :: Product f g a -> Product f g a -> Product f g a #

mconcat :: [Product f g a] -> Product f g a #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

Monoid r => Monoid (Forget r a b)

Via Monoid r => (a -> r)

Since: profunctors-5.6.2

Instance details

Defined in Data.Profunctor.Types

Methods

mempty :: Forget r a b #

mappend :: Forget r a b -> Forget r a b -> Forget r a b #

mconcat :: [Forget r a b] -> Forget r a b #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f (g a)) => Monoid (Compose f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

mempty :: Compose f g a #

mappend :: Compose f g a -> Compose f g a -> Compose f g a #

mconcat :: [Compose f g a] -> Compose f g a #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

type family Any :: k where ... #

The type constructor Any is type to which you can unsafely coerce any lifted type, and back. More concretely, for a lifted type t and value x :: t, -- unsafeCoerce (unsafeCoerce x :: Any) :: t is equivalent to x.

data ErrorMessage #

A description of a custom type error.

Constructors

ErrorMessage :<>: ErrorMessage infixl 6

Put two pieces of error message next to each other.

ErrorMessage :$$: ErrorMessage infixl 5

Stack two pieces of error message on top of each other.

Instances

Instances details
(TypeError x :: Constraint) => Fail (x :: ErrorMessage) Source # 
Instance details

Defined in Data.HList.FakePrelude

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
HEqBy HLeFn x y b => HEqBy HLeFn (Proxy x :: Type) (Proxy y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

Fail "Unvariant applied to empty variant" => Unvariant1 (b :: k) ('[] :: [Type]) (Proxy "Unvariant applied to empty variant") Source # 
Instance details

Defined in Data.HList.Variant

Methods

unvariant1 :: Proxy b -> Variant '[] -> Proxy "Unvariant applied to empty variant" Source #

Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

(HRevAppR l ('[] :: [Type]) ~ lRev, HExtendRs lRev (Proxy ('[] :: [Type])) ~ Proxy l1, l' ~ l1) => HBuild' l (Proxy l') Source #

see hEndP

Instance details

Defined in Data.HList.Record

Methods

hBuild' :: HList l -> Proxy l' Source #

(y ~ ReadP x, Read x) => ApplyAB ReadElement (Proxy x) y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: ReadElement -> Proxy x -> y Source #

(Read v, ShowLabel l, x ~ Tagged l v, ReadP x ~ y) => ApplyAB ReadComponent (Proxy x) y Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: ReadComponent -> Proxy x -> y Source #

Foldable (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' #

(>$) :: b -> Proxy b -> Proxy a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

HUnzip (Proxy :: [Type] -> Type) ls vs lvs => HZip (Proxy :: [Type] -> Type) ls vs lvs Source #

Missing from GHC-7.6.3 due to a bug:

let r = hEnd $ hBuild 1 2 3
*Data.HList> hZipList r r
H[(1,1),(2,2),(3,3)]
*Data.HList> hZip r r

<interactive>:30:1:
    Couldn't match type `Label k l' with `Integer'
    When using functional dependencies to combine
      HUnzip
        (Proxy [*]) ((':) * (Label k l) ls) ((':) * v vs) ((':) * lv lvs),
        arising from the dependency `xy -> x y'
        in the instance declaration at Data/HList/HListPrelude.hs:96:10
      HUnzip
        HList
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':)
           *
           (Integer, Integer)
           ((':) * (Integer, Integer) ((':) * (Integer, Integer) ('[] *)))),
        arising from a use of `hZip' at <interactive>:30:1-4
    In the expression: hZip r r
    In an equation for `it': it = hZip r r
Instance details

Defined in Data.HList.HListPrelude

Methods

hZip :: Proxy ls -> Proxy vs -> Proxy lvs Source #

HUnzip (Proxy :: [Type] -> Type) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HListPrelude

Methods

hUnzip :: Proxy '[] -> (Proxy '[], Proxy '[]) Source #

HLookupByHNat n l => Apply (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHLookupByHNat l) (Proxy n) Source #

(lv ~ Tagged l v, HUnzip (Proxy :: [Type] -> Type) ls vs lvs) => HUnzip (Proxy :: [Type] -> Type) (Label l ': ls) (v ': vs) (lv ': lvs) Source # 
Instance details

Defined in Data.HList.HListPrelude

Methods

hUnzip :: Proxy (lv ': lvs) -> (Proxy (Label l ': ls), Proxy (v ': vs)) Source #

Data t => Data (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) #

toConstr :: Proxy t -> Constr #

dataTypeOf :: Proxy t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) #

gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

HNat2Integral n => Show (Proxy n) Source # 
Instance details

Defined in Data.HList.TypeEqO

Methods

showsPrec :: Int -> Proxy n -> ShowS #

show :: Proxy n -> String #

showList :: [Proxy n] -> ShowS #

Show (Proxy 'False) Source # 
Instance details

Defined in Data.HList.TypeEqO

Show (Proxy 'True) Source # 
Instance details

Defined in Data.HList.TypeEqO

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

(ch ~ Proxy (HBoolEQ sel (KMember n ns)), Apply (ch, FHUProj sel ns) (HList (e ': l), Proxy n)) => Apply (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: FHUProj sel ns -> (HList (e ': l), Proxy n) -> ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (FHUProj sel ns) (HList l, Proxy ('HSucc n)) => Apply (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'False, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'True, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #
>>> let labelX = Label :: Label "x"
>>> let labelY = Label :: Label "y"
>>> let p = labelX .*. labelY .*. emptyProxy
>>> :t p
p :: Proxy '["x", "y"]
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let s = label6 .*. label3 .*. emptyProxy
>>> :t s
s :: Proxy '[Label "6", Label (Lbl 'HZero () ())]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (x ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (Lbl n' ns' desc' ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

HExtend (Label x) (Proxy ('[] :: [Type])) Source #

to keep types shorter, .*. used with Proxy avoids producing a Proxy :: Proxy '[Label x,Label y,Label z] if Proxy :: Proxy '[x,y,z] is not a kind error (as it is when mixing Label6 and Label3 labels).

ghc-7.6 does not accept Proxy ('[] :: [k]) so for now require k ~ *

Instance details

Defined in Data.HList.HListPrelude

Associated Types

type HExtendR (Label x) (Proxy '[]) Source #

Methods

(.*.) :: Label x -> Proxy '[] -> HExtendR (Label x) (Proxy '[]) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (x ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (x ': xs) -> HExtendR (to p q) (Proxy (x ': xs)) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

if the proxy has Data.HList.Label3.Lbl, then everything has to be wrapped in Label to make the kinds match up.

Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (Lbl n ns desc ': xs) -> HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy ('[] :: [Type])) Source #

Together with the instance below, this allows writing

makeLabelable "x y z"
p = x .*. y .*. z .*. emptyProxy

Or with HListPP

p = `x .*. `y .*. `z .*. emptyProxy

instead of

p = Proxy :: Proxy ["x","y","z"]
Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy '[]) Source #

Methods

(.*.) :: to p q -> Proxy '[] -> HExtendR (to p q) (Proxy '[]) Source #

EnsureLabel (Proxy x) (Label x) Source # 
Instance details

Defined in Data.HList.Labelable

Methods

toLabel :: Proxy x -> Label x Source #

HSplit l => HSplit ((e, Proxy 'False) ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT ((e, Proxy 'False) ': l) :: [Type] Source #

type HSplitF ((e, Proxy 'False) ': l) :: [Type] Source #

Methods

hSplit :: HList ((e, Proxy 'False) ': l) -> (HList (HSplitT ((e, Proxy 'False) ': l)), HList (HSplitF ((e, Proxy 'False) ': l))) Source #

HSplit l => HSplit ((e, Proxy 'True) ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT ((e, Proxy 'True) ': l) :: [Type] Source #

type HSplitF ((e, Proxy 'True) ': l) :: [Type] Source #

Methods

hSplit :: HList ((e, Proxy 'True) ': l) -> (HList (HSplitT ((e, Proxy 'True) ': l)), HList (HSplitF ((e, Proxy 'True) ': l))) Source #

HProxiesFD xs pxs => HProxiesFD (x ': xs) (Proxy x ': pxs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hProxies :: HList (Proxy x ': pxs) Source #

type HMemberP' pred e1 l (Proxy 'False) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP' pred e1 l (Proxy 'False) = HMemberP pred e1 l
type HMemberP' pred e1 l (Proxy 'True) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP' pred e1 l (Proxy 'True) = 'True
type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type DropProxy (Proxy x :: Type) Source # 
Instance details

Defined in Data.HList.HList

type DropProxy (Proxy x :: Type) = x
type ApplyR (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))
type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (Proxy (HBoolEQ sel (KMember n ns)), FHUProj sel ns) (HList (e ': l), Proxy n)
type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (FHUProj sel ns) (HList l, Proxy ('HSucc n))
type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) = HJust (e, (HList l, Proxy ('HSucc n)))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (y ': (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (y ': (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) = Proxy (Label (Lbl n ns desc) ': MapLabel (x ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) = Proxy (Lbl n ns desc ': (Lbl n' ns' desc' ': xs))
type HExtendR (Label x) (Proxy ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HListPrelude

type HExtendR (Label x) (Proxy ('[] :: [Type])) = Proxy '[x]
type HExtendR (to p q) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR (to p q) (Proxy (x ': xs))
type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs))
type HExtendR (to p q) (Proxy ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR (to p q) (Proxy ('[] :: [Type]))
type HNats (Proxy n ': l) Source # 
Instance details

Defined in Data.HList.HList

type HNats (Proxy n ': l) = n ': HNats l
type HSplitF ((e, Proxy 'False) ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitF ((e, Proxy 'False) ': l) = e ': HSplitF l
type HSplitF ((e, Proxy 'True) ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitF ((e, Proxy 'True) ': l) = HSplitF l
type HSplitT ((e, Proxy 'False) ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitT ((e, Proxy 'False) ': l) = HSplitT l
type HSplitT ((e, Proxy 'True) ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitT ((e, Proxy 'True) ': l) = e ': HSplitT l

data KProxy t #

A concrete, promotable proxy type, for use at the kind level. There are no instances for this because it is intended at the kind level only

Constructors

KProxy 

asProxyTypeOf :: a -> proxy a -> a #

asProxyTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

>>> import Data.Word
>>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8

Note the lower-case proxy in the definition. This allows any type constructor with just one argument to be passed to the function, for example we could also write

>>> import Data.Word
>>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8

reproxy :: forall {k1} {k2} proxy (a :: k1) (b :: k2). proxy a -> Proxy b #

Some times you need to change the proxy you have lying around. Idiomatic usage is to make a new combinator for the relationship between the proxies that you want to enforce, and define that combinator using reproxy.

data Succ n
reproxySucc :: proxy n -> Proxy (Succ n)
reproxySucc = reproxy

tagWith :: forall {k} proxy (s :: k) a. proxy s -> a -> Tagged s a #

Another way to convert a proxy to a tag.

unproxy :: forall {k} (s :: k) a. (Proxy s -> a) -> Tagged s a #

Convert from a representation based on a Proxy to a Tagged representation.

proxy :: forall {k} (s :: k) a proxy. Tagged s a -> proxy s -> a #

Convert from a Tagged representation to a representation based on a Proxy.

untagSelf :: Tagged a a -> a #

untagSelf is a type-restricted version of untag.

witness :: Tagged a b -> a -> b #

asTaggedTypeOf :: forall {k} s tagged (b :: k). s -> tagged s b -> s #

asTaggedTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

tagSelf :: a -> Tagged a a #

Tag a value with its own type.

untag :: forall {k} (s :: k) b. Tagged s b -> b #

Alias for unTagged

retag :: forall {k1} {k2} (s :: k1) b (t :: k2). Tagged s b -> Tagged t b #

Some times you need to change the tag you have lying around. Idiomatic usage is to make a new combinator for the relationship between the tags that you want to enforce, and define that combinator using retag.

data Succ n
retagSucc :: Tagged n a -> Tagged (Succ n) a
retagSucc = retag

newtype Tagged (s :: k) b #

A Tagged s b value is a value b with an attached phantom type s. This can be used in place of the more traditional but less safe idiom of passing in an undefined value with the type, because unlike an (s -> b), a Tagged s b can't try to use the argument s as a real value.

Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"

Tagged has kind k -> * -> * if the compiler supports PolyKinds, therefore there is an extra k showing in the instance haddocks that may cause confusion.

Constructors

Tagged 

Fields

Instances

Instances details
HasField' 'True (l :: k) (Tagged l v ': r) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel' :: Proxy 'True -> Label l -> HList (Tagged l v ': r) -> v Source #

HEqBy HLeFn x y b => HEqBy HLeFn (Tagged x v :: Type) (Tagged y w :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

(HEqK l l1 b, HasField' b l (Tagged l1 v1 ': r) v) => HasField (l :: k1) (Record (Tagged l1 v1 ': r)) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel :: Label l -> Record (Tagged l1 v1 ': r) -> v Source #

Label t ~ Label t' => SameLabels (Label t :: Type) (Tagged t' a :: Type) Source # 
Instance details

Defined in Data.HList.FakePrelude

SameLabels (Label t) s => SameLabels (Tagged t a :: Type) (s :: m) Source # 
Instance details

Defined in Data.HList.FakePrelude

(HRearrange3 ls rout r', r'' ~ (Tagged l v ': r'), ll ~ Label l) => HRearrange4 ll ls '[Tagged l v] rout r'' Source # 
Instance details

Defined in Data.HList.Record

Methods

hRearrange4 :: proxy ll -> Proxy ls -> HList '[Tagged l v] -> HList rout -> HList r'' Source #

(MapFieldTreeVal r ('Just xs) out2, FieldTreeVal v out1, (v ': HAppendListR out1 out2) ~ out) => MapFieldTreeVal r ('Just (Tagged n v ': xs)) out Source # 
Instance details

Defined in Data.HList.Dredge

(HMember (Label l) ks b, HCond b (Record r2) (Record (Tagged l v ': r2)) (Record r3), HDeleteLabels ks r1 r2) => HDeleteLabels ks (Tagged l v ': r1) r3 Source # 
Instance details

Defined in Data.HList.Record

Methods

hDeleteLabels :: proxy ks -> Record (Tagged l v ': r1) -> Record r3 Source #

(HMemberLabel l r1 b, UnionSymRec' b r1 (Tagged l v) r2' ru) => UnionSymRec r1 (Tagged l v ': r2') ru Source # 
Instance details

Defined in Data.HList.Record

Methods

unionSR :: Record r1 -> Record (Tagged l v ': r2') -> (Record ru, Record ru) Source #

Bifoldable (Tagged :: TYPE LiftedRep -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

bifold :: Monoid m => Tagged m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Tagged a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tagged a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tagged a b -> c #

Bifunctor (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

bimap :: (a -> b) -> (c -> d) -> Tagged a c -> Tagged b d #

first :: (a -> b) -> Tagged a c -> Tagged b c #

second :: (b -> c) -> Tagged a b -> Tagged a c #

Bitraversable (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tagged a b -> f (Tagged c d) #

Eq2 (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Tagged a c -> Tagged b d -> Bool #

Ord2 (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Tagged a c -> Tagged b d -> Ordering #

Read2 (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Tagged a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Tagged a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Tagged a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Tagged a b] #

Show2 (Tagged :: TYPE LiftedRep -> Type -> Type) 
Instance details

Defined in Data.Tagged

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Tagged a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Tagged a b] -> ShowS #

(Monoid x, Monoid (Variant (a ': b))) => Monoid (Variant (Tagged t x ': (a ': b))) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant (Tagged t x ': (a ': b)) #

mappend :: Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

mconcat :: [Variant (Tagged t x ': (a ': b))] -> Variant (Tagged t x ': (a ': b)) #

(Unvariant '[Tagged t x] x, Monoid x) => Monoid (Variant '[Tagged t x]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant '[Tagged t x] #

mappend :: Variant '[Tagged t x] -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

mconcat :: [Variant '[Tagged t x]] -> Variant '[Tagged t x] #

(Semigroup x, Semigroup (Variant (a ': b))) => Semigroup (Variant (Tagged t x ': (a ': b))) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(<>) :: Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

sconcat :: NonEmpty (Variant (Tagged t x ': (a ': b))) -> Variant (Tagged t x ': (a ': b)) #

stimes :: Integral b0 => b0 -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

(Unvariant '[Tagged t x] x, Semigroup x) => Semigroup (Variant '[Tagged t x]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(<>) :: Variant '[Tagged t x] -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

sconcat :: NonEmpty (Variant '[Tagged t x]) -> Variant '[Tagged t x] #

stimes :: Integral b => b -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

(Bounded x, Bounded z, HRevAppR (Tagged s x ': xs) ('[] :: [Type]) ~ (Tagged t z ': sx), MkVariant t z (Tagged s x ': xs)) => Bounded (Variant (Tagged s x ': xs)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

minBound :: Variant (Tagged s x ': xs) #

maxBound :: Variant (Tagged s x ': xs) #

(Enum x, Bounded x, Enum (Variant (y ': z))) => Enum (Variant (Tagged s x ': (y ': z))) Source #
>>> let t = minBound :: Variant '[Tagged "x" Bool, Tagged "y" Bool]
>>> [t .. maxBound]
[V{x=False},V{x=True},V{y=False},V{y=True}]
Odd behavior
There are some arguments that this instance should not exist.

The last type in the Variant does not need to be Bounded. This means that enumFrom behaves a bit unexpectedly:

>>> [False .. ]
[False,True]
>>> [t .. ]
[V{x=False},V{x=True},V{y=False},V{y=True},V{y=*** Exception: Prelude.Enum.Bool.toEnum: bad argument

This is a "feature" because it allows an Enum (Variant '[Tagged "a" Bool, Tagged "n" Integer])

Another difficult choice is that the lower bound is fromEnum 0 rather than minBound:

>>> take 5 [ minBound :: Variant '[Tagged "b" Bool, Tagged "i" Int] .. ]
[V{b=False},V{b=True},V{i=0},V{i=1},V{i=2}]
Instance details

Defined in Data.HList.Variant

Methods

succ :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) #

pred :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) #

toEnum :: Int -> Variant (Tagged s x ': (y ': z)) #

fromEnum :: Variant (Tagged s x ': (y ': z)) -> Int #

enumFrom :: Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromThen :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromTo :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromThenTo :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

Enum x => Enum (Variant '[Tagged s x]) Source #

While the instances could be written Enum (Variant '[]) Eq/Ord which cannot produce values, so they have instances for empty variants (unsafeEmptyVariant). Enum can produce values, so it is better that fromEnum 0 :: Variant '[] fails with No instance for Enum (Variant '[]) than producing an invalid variant.

Instance details

Defined in Data.HList.Variant

Methods

succ :: Variant '[Tagged s x] -> Variant '[Tagged s x] #

pred :: Variant '[Tagged s x] -> Variant '[Tagged s x] #

toEnum :: Int -> Variant '[Tagged s x] #

fromEnum :: Variant '[Tagged s x] -> Int #

enumFrom :: Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromThen :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromTo :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromThenTo :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

Choice (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Tagged a b -> Tagged (Either a c) (Either b c) #

right' :: Tagged a b -> Tagged (Either c a) (Either c b) #

Closed (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Tagged a b -> Tagged (x -> a) (x -> b) #

Costrong (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Tagged (a, d) (b, d) -> Tagged a b #

unsecond :: Tagged (d, a) (d, b) -> Tagged a b #

Profunctor (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d #

lmap :: (a -> b) -> Tagged b c -> Tagged a c #

rmap :: (b -> c) -> Tagged a b -> Tagged a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Tagged a b -> Tagged a c #

(.#) :: forall a b c q. Coercible b a => Tagged b c -> q a b -> Tagged a c #

Generic1 (Tagged s :: Type -> Type) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep1 (Tagged s) :: k -> Type #

Methods

from1 :: forall (a :: k). Tagged s a -> Rep1 (Tagged s) a #

to1 :: forall (a :: k). Rep1 (Tagged s) a -> Tagged s a #

Fail (ExtraField l) => HRearrange3 ('[] :: [Type]) (Tagged l v ': a) ('[] :: [Type]) Source #

For improved error messages

Instance details

Defined in Data.HList.Record

Methods

hRearrange3 :: proxy '[] -> HList (Tagged l v ': a) -> HList '[] Source #

Foldable (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

fold :: Monoid m => Tagged s m -> m #

foldMap :: Monoid m => (a -> m) -> Tagged s a -> m #

foldMap' :: Monoid m => (a -> m) -> Tagged s a -> m #

foldr :: (a -> b -> b) -> b -> Tagged s a -> b #

foldr' :: (a -> b -> b) -> b -> Tagged s a -> b #

foldl :: (b -> a -> b) -> b -> Tagged s a -> b #

foldl' :: (b -> a -> b) -> b -> Tagged s a -> b #

foldr1 :: (a -> a -> a) -> Tagged s a -> a #

foldl1 :: (a -> a -> a) -> Tagged s a -> a #

toList :: Tagged s a -> [a] #

null :: Tagged s a -> Bool #

length :: Tagged s a -> Int #

elem :: Eq a => a -> Tagged s a -> Bool #

maximum :: Ord a => Tagged s a -> a #

minimum :: Ord a => Tagged s a -> a #

sum :: Num a => Tagged s a -> a #

product :: Num a => Tagged s a -> a #

Eq1 (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

liftEq :: (a -> b -> Bool) -> Tagged s a -> Tagged s b -> Bool #

Ord1 (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

liftCompare :: (a -> b -> Ordering) -> Tagged s a -> Tagged s b -> Ordering #

Read1 (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tagged s a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tagged s a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tagged s a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tagged s a] #

Show1 (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tagged s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tagged s a] -> ShowS #

Traversable (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

traverse :: Applicative f => (a -> f b) -> Tagged s a -> f (Tagged s b) #

sequenceA :: Applicative f => Tagged s (f a) -> f (Tagged s a) #

mapM :: Monad m => (a -> m b) -> Tagged s a -> m (Tagged s b) #

sequence :: Monad m => Tagged s (m a) -> m (Tagged s a) #

Applicative (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

pure :: a -> Tagged s a #

(<*>) :: Tagged s (a -> b) -> Tagged s a -> Tagged s b #

liftA2 :: (a -> b -> c) -> Tagged s a -> Tagged s b -> Tagged s c #

(*>) :: Tagged s a -> Tagged s b -> Tagged s b #

(<*) :: Tagged s a -> Tagged s b -> Tagged s a #

Functor (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

fmap :: (a -> b) -> Tagged s a -> Tagged s b #

(<$) :: a -> Tagged s b -> Tagged s a #

Monad (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

(>>=) :: Tagged s a -> (a -> Tagged s b) -> Tagged s b #

(>>) :: Tagged s a -> Tagged s b -> Tagged s b #

return :: a -> Tagged s a #

Comonad (Tagged s) 
Instance details

Defined in Control.Comonad

Methods

extract :: Tagged s a -> a #

duplicate :: Tagged s a -> Tagged s (Tagged s a) #

extend :: (Tagged s a -> b) -> Tagged s a -> Tagged s b #

(MapFieldTree ('Just xs) vs3, FieldTree v vs1, MapCons (Label n) (('[] :: [Type]) ': vs1) vs2, HAppendListR vs2 vs3 ~ vs) => MapFieldTree ('Just (Tagged n v ': xs)) vs Source #

recursive case

Instance details

Defined in Data.HList.Dredge

(RecordLabelsStr xs, ShowLabel x) => RecordLabelsStr (Tagged x t ': xs) Source # 
Instance details

Defined in Data.HList.Data

Methods

recordLabelsStr :: Record (Tagged x t ': xs) -> [String] Source #

HSplit l => HSplit (Tagged 'False e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT (Tagged 'False e ': l) :: [Type] Source #

type HSplitF (Tagged 'False e ': l) :: [Type] Source #

Methods

hSplit :: HList (Tagged 'False e ': l) -> (HList (HSplitT (Tagged 'False e ': l)), HList (HSplitF (Tagged 'False e ': l))) Source #

HSplit l => HSplit (Tagged 'True e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT (Tagged 'True e ': l) :: [Type] Source #

type HSplitF (Tagged 'True e ': l) :: [Type] Source #

Methods

hSplit :: HList (Tagged 'True e ': l) -> (HList (HSplitT (Tagged 'True e ': l)), HList (HSplitF (Tagged 'True e ': l))) Source #

(SameLength' r (RecordValuesR r), SameLength' (RecordValuesR r) r, RecordValues r) => RecordValues (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

Associated Types

type RecordValuesR (Tagged l v ': r) :: [Type] Source #

Methods

recordValues' :: HList (Tagged l v ': r) -> HList (RecordValuesR (Tagged l v ': r)) Source #

(ShowLabel l, Show v, ShowComponents r) => ShowComponents (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

Methods

showComponents :: String -> HList (Tagged l v ': r) -> String Source #

(ShowLabel l, Read v, ReadVariant vs, HOccursNot (Label l) (LabelsOf vs)) => ReadVariant (Tagged l v ': vs) Source # 
Instance details

Defined in Data.HList.Variant

Methods

readVariant :: ReadP (Variant (Tagged l v ': vs)) Source #

(ShowLabel l, Show v, ShowVariant (w ': ws)) => ShowVariant (Tagged l v ': (w ': ws)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

showVariant :: Variant (Tagged l v ': (w ': ws)) -> ShowS Source #

(ShowLabel l, VariantConstrs xs) => VariantConstrs (Tagged l e ': xs) Source # 
Instance details

Defined in Data.HList.Variant

Methods

variantConstrs :: DataType -> proxy (Tagged l e ': xs) -> [Constr] Source #

(Data s, Data b) => Data (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Tagged s b -> c (Tagged s b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tagged s b) #

toConstr :: Tagged s b -> Constr #

dataTypeOf :: Tagged s b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tagged s b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tagged s b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tagged s b -> Tagged s b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagged s b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tagged s b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagged s b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged s b -> m (Tagged s b) #

IsString a => IsString (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

fromString :: String -> Tagged s a #

Storable a => Storable (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

sizeOf :: Tagged s a -> Int #

alignment :: Tagged s a -> Int #

peekElemOff :: Ptr (Tagged s a) -> Int -> IO (Tagged s a) #

pokeElemOff :: Ptr (Tagged s a) -> Int -> Tagged s a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Tagged s a) #

pokeByteOff :: Ptr b -> Int -> Tagged s a -> IO () #

peek :: Ptr (Tagged s a) -> IO (Tagged s a) #

poke :: Ptr (Tagged s a) -> Tagged s a -> IO () #

(Semigroup a, Monoid a) => Monoid (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

mempty :: Tagged s a #

mappend :: Tagged s a -> Tagged s a -> Tagged s a #

mconcat :: [Tagged s a] -> Tagged s a #

Semigroup a => Semigroup (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

(<>) :: Tagged s a -> Tagged s a -> Tagged s a #

sconcat :: NonEmpty (Tagged s a) -> Tagged s a #

stimes :: Integral b => b -> Tagged s a -> Tagged s a #

Bits a => Bits (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

(.&.) :: Tagged s a -> Tagged s a -> Tagged s a #

(.|.) :: Tagged s a -> Tagged s a -> Tagged s a #

xor :: Tagged s a -> Tagged s a -> Tagged s a #

complement :: Tagged s a -> Tagged s a #

shift :: Tagged s a -> Int -> Tagged s a #

rotate :: Tagged s a -> Int -> Tagged s a #

zeroBits :: Tagged s a #

bit :: Int -> Tagged s a #

setBit :: Tagged s a -> Int -> Tagged s a #

clearBit :: Tagged s a -> Int -> Tagged s a #

complementBit :: Tagged s a -> Int -> Tagged s a #

testBit :: Tagged s a -> Int -> Bool #

bitSizeMaybe :: Tagged s a -> Maybe Int #

bitSize :: Tagged s a -> Int #

isSigned :: Tagged s a -> Bool #

shiftL :: Tagged s a -> Int -> Tagged s a #

unsafeShiftL :: Tagged s a -> Int -> Tagged s a #

shiftR :: Tagged s a -> Int -> Tagged s a #

unsafeShiftR :: Tagged s a -> Int -> Tagged s a #

rotateL :: Tagged s a -> Int -> Tagged s a #

rotateR :: Tagged s a -> Int -> Tagged s a #

popCount :: Tagged s a -> Int #

FiniteBits a => FiniteBits (Tagged s a) 
Instance details

Defined in Data.Tagged

Bounded b => Bounded (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

minBound :: Tagged s b #

maxBound :: Tagged s b #

Enum a => Enum (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

succ :: Tagged s a -> Tagged s a #

pred :: Tagged s a -> Tagged s a #

toEnum :: Int -> Tagged s a #

fromEnum :: Tagged s a -> Int #

enumFrom :: Tagged s a -> [Tagged s a] #

enumFromThen :: Tagged s a -> Tagged s a -> [Tagged s a] #

enumFromTo :: Tagged s a -> Tagged s a -> [Tagged s a] #

enumFromThenTo :: Tagged s a -> Tagged s a -> Tagged s a -> [Tagged s a] #

Floating a => Floating (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

pi :: Tagged s a #

exp :: Tagged s a -> Tagged s a #

log :: Tagged s a -> Tagged s a #

sqrt :: Tagged s a -> Tagged s a #

(**) :: Tagged s a -> Tagged s a -> Tagged s a #

logBase :: Tagged s a -> Tagged s a -> Tagged s a #

sin :: Tagged s a -> Tagged s a #

cos :: Tagged s a -> Tagged s a #

tan :: Tagged s a -> Tagged s a #

asin :: Tagged s a -> Tagged s a #

acos :: Tagged s a -> Tagged s a #

atan :: Tagged s a -> Tagged s a #

sinh :: Tagged s a -> Tagged s a #

cosh :: Tagged s a -> Tagged s a #

tanh :: Tagged s a -> Tagged s a #

asinh :: Tagged s a -> Tagged s a #

acosh :: Tagged s a -> Tagged s a #

atanh :: Tagged s a -> Tagged s a #

log1p :: Tagged s a -> Tagged s a #

expm1 :: Tagged s a -> Tagged s a #

log1pexp :: Tagged s a -> Tagged s a #

log1mexp :: Tagged s a -> Tagged s a #

RealFloat a => RealFloat (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

floatRadix :: Tagged s a -> Integer #

floatDigits :: Tagged s a -> Int #

floatRange :: Tagged s a -> (Int, Int) #

decodeFloat :: Tagged s a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Tagged s a #

exponent :: Tagged s a -> Int #

significand :: Tagged s a -> Tagged s a #

scaleFloat :: Int -> Tagged s a -> Tagged s a #

isNaN :: Tagged s a -> Bool #

isInfinite :: Tagged s a -> Bool #

isDenormalized :: Tagged s a -> Bool #

isNegativeZero :: Tagged s a -> Bool #

isIEEE :: Tagged s a -> Bool #

atan2 :: Tagged s a -> Tagged s a -> Tagged s a #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type #

Methods

from :: Tagged s b -> Rep (Tagged s b) x #

to :: Rep (Tagged s b) x -> Tagged s b #

Ix b => Ix (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

range :: (Tagged s b, Tagged s b) -> [Tagged s b] #

index :: (Tagged s b, Tagged s b) -> Tagged s b -> Int #

unsafeIndex :: (Tagged s b, Tagged s b) -> Tagged s b -> Int #

inRange :: (Tagged s b, Tagged s b) -> Tagged s b -> Bool #

rangeSize :: (Tagged s b, Tagged s b) -> Int #

unsafeRangeSize :: (Tagged s b, Tagged s b) -> Int #

Num a => Num (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

(+) :: Tagged s a -> Tagged s a -> Tagged s a #

(-) :: Tagged s a -> Tagged s a -> Tagged s a #

(*) :: Tagged s a -> Tagged s a -> Tagged s a #

negate :: Tagged s a -> Tagged s a #

abs :: Tagged s a -> Tagged s a #

signum :: Tagged s a -> Tagged s a #

fromInteger :: Integer -> Tagged s a #

Read b => Read (Tagged s b) 
Instance details

Defined in Data.Tagged

Fractional a => Fractional (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

(/) :: Tagged s a -> Tagged s a -> Tagged s a #

recip :: Tagged s a -> Tagged s a #

fromRational :: Rational -> Tagged s a #

Integral a => Integral (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

quot :: Tagged s a -> Tagged s a -> Tagged s a #

rem :: Tagged s a -> Tagged s a -> Tagged s a #

div :: Tagged s a -> Tagged s a -> Tagged s a #

mod :: Tagged s a -> Tagged s a -> Tagged s a #

quotRem :: Tagged s a -> Tagged s a -> (Tagged s a, Tagged s a) #

divMod :: Tagged s a -> Tagged s a -> (Tagged s a, Tagged s a) #

toInteger :: Tagged s a -> Integer #

Real a => Real (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

toRational :: Tagged s a -> Rational #

RealFrac a => RealFrac (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

properFraction :: Integral b => Tagged s a -> (b, Tagged s a) #

truncate :: Integral b => Tagged s a -> b #

round :: Integral b => Tagged s a -> b #

ceiling :: Integral b => Tagged s a -> b #

floor :: Integral b => Tagged s a -> b #

Show b => Show (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

showsPrec :: Int -> Tagged s b -> ShowS #

show :: Tagged s b -> String #

showList :: [Tagged s b] -> ShowS #

NFData b => NFData (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

rnf :: Tagged s b -> () #

Eq b => Eq (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

(==) :: Tagged s b -> Tagged s b -> Bool #

(/=) :: Tagged s b -> Tagged s b -> Bool #

Ord b => Ord (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

compare :: Tagged s b -> Tagged s b -> Ordering #

(<) :: Tagged s b -> Tagged s b -> Bool #

(<=) :: Tagged s b -> Tagged s b -> Bool #

(>) :: Tagged s b -> Tagged s b -> Bool #

(>=) :: Tagged s b -> Tagged s b -> Bool #

max :: Tagged s b -> Tagged s b -> Tagged s b #

min :: Tagged s b -> Tagged s b -> Tagged s b #

(MkVariant l e v, Data e, GunfoldVariant (b ': bs) v) => GunfoldVariant (Tagged l e ': (b ': bs)) v Source # 
Instance details

Defined in Data.HList.Variant

Methods

gunfoldVariant :: (forall b0. Data b0 => (b0 -> Variant v) -> c (Variant v)) -> Proxy (Tagged l e ': (b ': bs)) -> Int -> c (Variant v) Source #

(MkVariant l e v, Data e) => GunfoldVariant '[Tagged l e] v Source # 
Instance details

Defined in Data.HList.Variant

Methods

gunfoldVariant :: (forall b. Data b => (b -> Variant v) -> c (Variant v)) -> Proxy '[Tagged l e] -> Int -> c (Variant v) Source #

(HEq a a' b, HAllEqVal (Tagged t a' ': xs) b2, HAnd b b2 ~ b3) => HAllEqVal (Tagged s a ': (Tagged t a' ': xs)) b3 Source # 
Instance details

Defined in Data.HList.Variant

(HMemberM (Label l1) (l ': ls) b, H2ProjectByLabels' b (l ': ls) (Tagged l1 v1 ': r1) rin rout) => H2ProjectByLabels (l ': ls) (Tagged l1 v1 ': r1) rin rout Source # 
Instance details

Defined in Data.HList.Record

Methods

h2projectByLabels :: proxy (l ': ls) -> HList (Tagged l1 v1 ': r1) -> (HList rin, HList rout) Source #

HZipRecord as bs abss => HZipRecord (Tagged x a ': as) (Tagged x b ': bs) (Tagged x (a, b) ': abss) Source # 
Instance details

Defined in Data.HList.Record

Methods

hZipRecord :: Record (Tagged x a ': as) -> Record (Tagged x b ': bs) -> Record (Tagged x (a, b) ': abss) Source #

hUnzipRecord :: Record (Tagged x (a, b) ': abss) -> (Record (Tagged x a ': as), Record (Tagged x b ': bs)) Source #

type Rep1 (Tagged s :: Type -> Type) 
Instance details

Defined in Data.Tagged

type Rep1 (Tagged s :: Type -> Type) = D1 ('MetaData "Tagged" "Data.Tagged" "tagged-0.8.8-D9s63x51vSh3cVaEBmve02" 'True) (C1 ('MetaCons "Tagged" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTagged") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type HSplitF (Tagged 'False e ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitF (Tagged 'False e ': l) = e ': HSplitF l
type HSplitF (Tagged 'True e ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitF (Tagged 'True e ': l) = HSplitF l
type HSplitT (Tagged 'False e ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitT (Tagged 'False e ': l) = HSplitT l
type HSplitT (Tagged 'True e ': l) Source # 
Instance details

Defined in Data.HList.HList

type HSplitT (Tagged 'True e ': l) = e ': HSplitT l
type LabelsOf (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

type LabelsOf (Tagged l v ': r) = Label l ': LabelsOf r
type RecordValuesR (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

type RecordValuesR (Tagged l v ': r) = v ': RecordValuesR r
type GetElemTy (Tagged label v ': rest) Source # 
Instance details

Defined in Data.HList.RecordU

type GetElemTy (Tagged label v ': rest) = v
type Untag1 (Tagged k2 x) Source # 
Instance details

Defined in Data.HList.TIP

type Untag1 (Tagged k2 x) = x
type UntagR (Tagged y y ': ys) Source # 
Instance details

Defined in Data.HList.TIP

type UntagR (Tagged y y ': ys) = y ': UntagR ys
type UnMaybe (Tagged l (Maybe e)) Source # 
Instance details

Defined in Data.HList.Variant

type UnMaybe (Tagged l (Maybe e)) = Tagged l e
type Rep (Tagged s b) 
Instance details

Defined in Data.Tagged

type Rep (Tagged s b) = D1 ('MetaData "Tagged" "Data.Tagged" "tagged-0.8.8-D9s63x51vSh3cVaEBmve02" 'True) (C1 ('MetaCons "Tagged" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTagged") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))
type HMapOutV_gety (Tagged s x ': xs) z Source # 
Instance details

Defined in Data.HList.Variant

type HMapOutV_gety (Tagged s x ': xs) z = Tagged s z ': HMapOutV_gety xs z
type ZipVRCxt (Tagged s f ': fs) (Tagged s x ': xs) (Tagged s y ': ys) Source # 
Instance details

Defined in Data.HList.Variant

type ZipVRCxt (Tagged s f ': fs) (Tagged s x ': xs) (Tagged s y ': ys) = (f ~ (x -> y), ZipVRCxt fs xs ys)

type family ZipTagged (ts :: [k]) (vs :: [*]) :: [*] Source #

see Data.HList.Record.zipTagged

Instances

Instances details
type ZipTagged ('[] :: [k]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type ZipTagged ('[] :: [k]) ('[] :: [Type]) = '[] :: [Type]
type ZipTagged (t ': ts :: [Symbol]) (v ': vs) Source # 
Instance details

Defined in Data.HList.FakePrelude

type ZipTagged (t ': ts :: [Symbol]) (v ': vs) = Tagged t v ': ZipTagged ts vs
type ZipTagged (Label t ': ts :: [Type]) (v ': vs) Source # 
Instance details

Defined in Data.HList.FakePrelude

type ZipTagged (Label t ': ts :: [Type]) (v ': vs) = Tagged t v ': ZipTagged ts vs
type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) Source # 
Instance details

Defined in Data.HList.Label3

type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) = Tagged (Lbl ix ns n) v ': ZipTagged ts vs

class HAllTaggedLV (ps :: [*]) Source #

The Record, Variant, TIP, TIC type constructors only make sense when they are applied to an instance of this class

Instances

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

Defined in Data.HList.FakePrelude

(HAllTaggedLV xs, x ~ Tagged t v) => HAllTaggedLV (x ': xs) Source # 
Instance details

Defined in Data.HList.FakePrelude

class SameLabels (x :: k) (y :: m) Source #

Instances

Instances details
SameLabels (Label t) s => SameLabels (t :: Symbol) (s :: m) Source # 
Instance details

Defined in Data.HList.FakePrelude

Label t ~ Label t' => SameLabels (Label t :: Type) (t' :: Symbol) Source # 
Instance details

Defined in Data.HList.FakePrelude

Label t ~ Label t' => SameLabels (Label t :: Type) (Label t' :: Type) Source # 
Instance details

Defined in Data.HList.FakePrelude

Label t ~ Label (Lbl ix ns n) => SameLabels (Label t :: Type) (Lbl ix ns n :: Type) Source # 
Instance details

Defined in Data.HList.Label3

Label t ~ Label t' => SameLabels (Label t :: Type) (Tagged t' a :: Type) Source # 
Instance details

Defined in Data.HList.FakePrelude

SameLabels (Label t) s => SameLabels (Tagged t a :: Type) (s :: m) Source # 
Instance details

Defined in Data.HList.FakePrelude

SameLabels ('[] :: [k1]) ('[] :: [k2]) Source # 
Instance details

Defined in Data.HList.FakePrelude

SameLabels ('[] :: [k]) (x ': xs :: [a]) Source # 
Instance details

Defined in Data.HList.FakePrelude

SameLabels (x ': xs :: [a]) ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.FakePrelude

(SameLabels x y, SameLabels xs ys) => SameLabels (x ': xs :: [a1]) (y ': ys :: [a2]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type family SameLengths (xs :: [[k]]) :: Constraint Source #

Instances

Instances details
type SameLengths ('[] :: [[k]]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type SameLengths ('[] :: [[k]]) = ()
type SameLengths (x ': (y ': ys) :: [[k]]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type SameLengths (x ': (y ': ys) :: [[k]]) = (SameLength x y, SameLengths (y ': ys))
type SameLengths ('[x] :: [[k]]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type SameLengths ('[x] :: [[k]]) = ()

class (SameLength' x y, SameLength' y x) => SameLength (x :: [k]) (y :: [m]) where Source #

symmetrical version of SameLength'. Written as a class instead of

type SameLength a b = (SameLength' a b, SameLength' b a)

since ghc expands type synonyms, but not classes (and it seems to have the same result)

Minimal complete definition

Nothing

Methods

sameLength :: (r x `p` f (q y)) -> r x `p` f (q y) Source #

SameLength x y => Equality (r x) (q y) (r x) (q y)

used like simple, except it restricts the type-level lists involved to have the same length, without fixing the type of container or the elements in the list.

Instances

Instances details
(SameLength' x y, SameLength' y x) => SameLength (x :: [k]) (y :: [m]) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

sameLength :: forall {k1} {k2} {k3} p (r :: [k0] -> k1) (f :: k3 -> k2) (q :: [m0] -> k3). p (r x) (f (q y)) -> p (r x) (f (q y)) Source #

class SameLength' (es1 :: [k]) (es2 :: [m]) Source #

Ensure two lists have the same length. We do case analysis on the first one (hence the type must be known to the type checker). In contrast, the second list may be a type variable.

Instances

Instances details
es2 ~ ('[] :: [m]) => SameLength' ('[] :: [k]) (es2 :: [m]) Source # 
Instance details

Defined in Data.HList.FakePrelude

(SameLength' xs ys, es2 ~ (y ': ys)) => SameLength' (x ': xs :: [k]) (es2 :: [m]) Source # 
Instance details

Defined in Data.HList.FakePrelude

type TypeablePolyK (a :: k) = Typeable a Source #

type ExtraField x = ErrText "extra field" :<>: ErrShowType x Source #

type HNatIndexTooLarge (nat :: HNat) (r :: [k] -> *) (xs :: [k]) = ((ErrText "0-based index" :<>: ErrShowType (HNat2Nat nat)) :<>: ErrText "is too large for collection") :$$: ErrShowType (r xs) Source #

type ExcessFieldFound key collection = (ErrText "found field" :<>: ErrShowType key) :$$: (ErrText "when it should be absent from" :<>: ErrShowType collection) Source #

type FieldNotFound key collection = (ErrText "key" :<>: ErrShowType key) :$$: (ErrText "could not be found in" :<>: ErrShowType collection) Source #

type ErrText x = Text x Source #

use the alias ErrText to prevent conflicts with Data.Text

GHC.TypeLits.:<>: and GHC.TypeLits.:$$: are re-exported

class Fail (x :: k) Source #

A class without instances for explicit failure.

Note that with ghc>=8.0, `x :: TypeError` which is formatted properly. Otherwise x is made of nested (left-associated) promoted tuples. For example:

(x ~ '( '( '("the", Int), "is wrong") ) ) :: ((,) Symbol *, Symbol)

Therefore code that works across ghc-7.6 through ghc-8.0 needs to use ErrText, ErrShowType, :<>:, :$$: to construct the type x.

Instances

Instances details
(TypeError x :: Constraint) => Fail (x :: ErrorMessage) Source # 
Instance details

Defined in Data.HList.FakePrelude

class HCast1 (b :: Bool) x y where Source #

helper for HCast

Methods

hCast1 :: Proxy b -> x -> Maybe y Source #

Instances

Instances details
HCast1 'False x y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hCast1 :: Proxy 'False -> x -> Maybe y Source #

x ~ y => HCast1 'True x y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hCast1 :: Proxy 'True -> x -> Maybe y Source #

class HCast x y where Source #

Named after cast, which behaves the same at runtime. One difference is that there is a HCast instance for every type, while Typeable instances can be missing sometimes.

Methods

hCast :: x -> Maybe y Source #

Instances

Instances details
(HEq x y b, HCast1 b x y) => HCast x y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hCast :: x -> Maybe y Source #

class ArityRev (f :: *) (n :: HNat) Source #

given the number of arguments a function can take, make sure the function type actually matches

Instances

Instances details
ArityRev f 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

(xf ~ (x -> f), ArityRev f n) => ArityRev xf ('HSucc n) Source # 
Instance details

Defined in Data.HList.FakePrelude

class ArityFwd (f :: *) (n :: HNat) | f -> n Source #

calculate the number of arguments a function can take

Instances

Instances details
hZero ~ 'HZero => ArityFwd f hZero Source # 
Instance details

Defined in Data.HList.TypeEqO

Arity f n => ArityFwd (x -> f) ('HSucc n) Source # 
Instance details

Defined in Data.HList.TypeEqO

type Arity f n = (ArityFwd f n, ArityRev f n) Source #

class HEqByFn f Source #

Every instance of this class should have an instance of HEqBy

Instances

Instances details
HEqByFn HLeFn Source # 
Instance details

Defined in Data.HList.HSort

HEqByFn EqTagValue Source # 
Instance details

Defined in Data.HList.RecordU

HEqByFn a => HEqByFn (HDown a :: Type) Source # 
Instance details

Defined in Data.HList.HSort

HEqByFn a => HEqByFn (HNeq a :: Type) Source # 
Instance details

Defined in Data.HList.HSort

class HEqByFn f => HEqBy (f :: t) (x :: k) (y :: k) (b :: Bool) | f x y -> b Source #

this class generalizes HEq by allowing the choice of f to allow equating only part of x and y

Instances

Instances details
HLe x y ~ b => HEqBy HLeFn (x :: HNat) (y :: HNat) b Source # 
Instance details

Defined in Data.HList.HSort

(HEq (CmpSymbol x y) 'GT nb, HNot nb ~ b) => HEqBy HLeFn (x :: Symbol) (y :: Symbol) b Source #

only in ghc >= 7.7

>>> let b1 = Proxy :: HEqBy HLeFn "x" "y" b => Proxy b
>>> :t b1
b1 :: Proxy 'True
>>> let b2 = Proxy :: HEqBy HLeFn "x" "x" b => Proxy b
>>> :t b2
b2 :: Proxy 'True
>>> let b3 = Proxy :: HEqBy HLeFn "y" "x" b => Proxy b
>>> :t b3
b3 :: Proxy 'False
Instance details

Defined in Data.HList.HSort

(txv ~ Tagged x v, tyw ~ Tagged y w, HEq v w b) => HEqBy EqTagValue (txv :: Type) (tyw :: Type) b Source # 
Instance details

Defined in Data.HList.RecordU

(x <=? y) ~ b => HEqBy HLeFn (x :: k) (y :: k) b Source #

only in ghc >= 7.7

Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Label x :: Type) (Label y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Proxy x :: Type) (Proxy y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

(HEqBy HLeFn n m b, ns ~ ns') => HEqBy HLeFn (Lbl n ns desc :: Type) (Lbl m ns' desc' :: Type) b Source #

Data.HList.Label3 labels can only be compared if they belong to the same namespace.

Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Tagged x v :: Type) (Tagged y w :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

HEqBy f y x b => HEqBy (HDown f :: Type) (x :: k2) (y :: k2) b Source # 
Instance details

Defined in Data.HList.HSort

(HEqBy le y x b1, HNot b1 ~ b2) => HEqBy (HNeq le :: Type) (x :: k2) (y :: k2) b2 Source # 
Instance details

Defined in Data.HList.HSort

type HEqK (x :: k1) (y :: k2) (b :: Bool) = HEq (Proxy x) (Proxy y) b Source #

Equality for types that may have different kinds. This definition allows operations on Record [Tagged "x" a, Tagged 2 b] to work as expected.

class HEq (x :: k) (y :: k) (b :: Bool) | x y -> b Source #

We have to use Functional dependencies for now, for the sake of the generic equality.

Instances

Instances details
HEq (x :: k) (x :: k) 'True Source # 
Instance details

Defined in Data.HList.TypeEqO

'False ~ b => HEq (x :: k) (y :: k) b Source # 
Instance details

Defined in Data.HList.TypeEqO

newtype HJust x Source #

Constructors

HJust x 

Instances

Instances details
(Apply p s, HUnfoldFD p (ApplyR p s) z) => HUnfoldFD p (HJust (e, s)) (e ': z) Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnfold' :: p -> HJust (e, s) -> HList (e ': z) Source #

Show x => Show (HJust x) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

showsPrec :: Int -> HJust x -> ShowS #

show :: HJust x -> String #

showList :: [HJust x] -> ShowS #

hJustA ~ HJust a => ApplyAB (HJust t) a hJustA Source #

HJust () is a placeholder for a function that applies the HJust constructor

Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HJust t -> a -> hJustA Source #

FromHJust l => FromHJust (HJust e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type FromHJustR (HJust e ': l) :: [Type] Source #

Methods

fromHJust :: HList (HJust e ': l) -> HList (FromHJustR (HJust e ': l)) Source #

type HUnfoldR p (HJust (e, s)) Source # 
Instance details

Defined in Data.HList.HList

type HUnfoldR p (HJust (e, s)) = e ': HUnfoldR p (ApplyR p s)
type FromHJustR (HJust e ': l) Source # 
Instance details

Defined in Data.HList.HList

type FromHJustR (HJust e ': l) = e ': FromHJustR l

data HNothing Source #

Constructors

HNothing 

Instances

Instances details
Show HNothing Source # 
Instance details

Defined in Data.HList.FakePrelude

HUnfoldFD p HNothing ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnfold' :: p -> HNothing -> HList '[] Source #

FromHJust l => FromHJust (HNothing ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type FromHJustR (HNothing ': l) :: [Type] Source #

Methods

fromHJust :: HList (HNothing ': l) -> HList (FromHJustR (HNothing ': l)) Source #

type HUnfoldR p HNothing Source # 
Instance details

Defined in Data.HList.HList

type HUnfoldR p HNothing = '[] :: [Type]
type FromHJustR (HNothing ': l) Source # 
Instance details

Defined in Data.HList.HList

type family HDiv2 (x :: HNat) :: HNat Source #

HDiv2 x behaves like x div 2

Instances

Instances details
type HDiv2 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HDiv2 'HZero = 'HZero
type HDiv2 ('HSucc ('HSucc a)) Source # 
Instance details

Defined in Data.HList.FakePrelude

type HDiv2 ('HSucc ('HSucc a)) = 'HSucc (HDiv2 a)
type HDiv2 ('HSucc 'HZero) Source # 
Instance details

Defined in Data.HList.FakePrelude

type HDiv2 ('HSucc 'HZero) = 'HZero

type family HLe (x :: HNat) (y :: HNat) :: Bool Source #

Less than or equal to

Instances

Instances details
type HLe 'HZero 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLe 'HZero 'HZero = 'True
type HLe ('HSucc x) y Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLe ('HSucc x) y = HLt x y

type family HLt (x :: HNat) (y :: HNat) :: Bool Source #

Less than

Instances

Instances details
type HLt 'HZero 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLt 'HZero 'HZero = 'False
type HLt 'HZero ('HSucc n) Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLt 'HZero ('HSucc n) = 'True
type HLt ('HSucc n) 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLt ('HSucc n) 'HZero = 'False
type HLt ('HSucc n) ('HSucc n') Source # 
Instance details

Defined in Data.HList.FakePrelude

type HLt ('HSucc n) ('HSucc n') = HLt n n'

type family HNatEq (t1 :: HNat) (t2 :: HNat) :: Bool Source #

Equality on natural numbers (eventually to be subsumed by the universal polykinded HEq)

Instances

Instances details
type HNatEq 'HZero 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNatEq 'HZero ('HSucc n) Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNatEq 'HZero ('HSucc n) = 'False
type HNatEq ('HSucc n) 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNatEq ('HSucc n) 'HZero = 'False
type HNatEq ('HSucc n) ('HSucc n') Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNatEq ('HSucc n) ('HSucc n') = HNatEq n n'

class HNats2Integrals (ns :: [HNat]) where Source #

Methods

hNats2Integrals :: Integral i => Proxy ns -> [i] Source #

Instances

Instances details
HNats2Integrals ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hNats2Integrals :: Integral i => Proxy '[] -> [i] Source #

(HNats2Integrals ns, HNat2Integral n) => HNats2Integrals (n ': ns) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hNats2Integrals :: Integral i => Proxy (n ': ns) -> [i] Source #

type family HNat2Nat (n :: HNat) :: Nat Source #

Instances

Instances details
type HNat2Nat 'HZero Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNat2Nat 'HZero = 0
type HNat2Nat ('HSucc n) Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNat2Nat ('HSucc n) = 1 + HNat2Nat n

class HNat2Integral (n :: HNat) where Source #

Methods

hNat2Integral :: Integral i => Proxy n -> i Source #

Instances

Instances details
KnownNat (HNat2Nat n) => HNat2Integral n Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hNat2Integral :: Integral i => Proxy n -> i Source #

data HNat Source #

The data type to be lifted to the type level

Constructors

HZero 
HSucc HNat 

Instances

Instances details
xxs ~ ('[] :: [Type]) => HLengthEq1 xxs 'HZero Source # 
Instance details

Defined in Data.HList.HList

HLe x y ~ b => HEqBy HLeFn (x :: HNat) (y :: HNat) b Source # 
Instance details

Defined in Data.HList.HSort

(HLengthEq xs n, xxs ~ (x ': xs)) => HLengthEq1 xxs ('HSucc n :: HNat) Source # 
Instance details

Defined in Data.HList.HList

zero ~ 'HZero => HLengthEq2 ('[] :: [Type]) (zero :: HNat) Source # 
Instance details

Defined in Data.HList.HList

HFindMany ('[] :: [k]) (r :: [k]) ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.RecordU

(HLengthEq xs n, sn ~ 'HSucc n) => HLengthEq2 (x ': xs) (sn :: HNat) Source # 
Instance details

Defined in Data.HList.HList

(HFind l r n, HFindMany ls r ns) => HFindMany (l ': ls :: [k]) (r :: [k]) (n ': ns) Source # 
Instance details

Defined in Data.HList.RecordU

HNats2Integrals ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hNats2Integrals :: Integral i => Proxy '[] -> [i] Source #

HTypes2HNats ('[] :: [Type]) (l :: [Type]) ('[] :: [HNat]) Source #

And lift to the list of types

Instance details

Defined in Data.HList.HTypeIndexed

(HType2HNat e l n, HTypes2HNats es l ns) => HTypes2HNats (e ': es :: [Type]) (l :: [Type]) (n ': ns) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

HLookupByHNat n l => Apply (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHLookupByHNat l) (Proxy n) Source #

HNat2Integral n => Show (Proxy n) Source # 
Instance details

Defined in Data.HList.TypeEqO

Methods

showsPrec :: Int -> Proxy n -> ShowS #

show :: Proxy n -> String #

showList :: [Proxy n] -> ShowS #

(ch ~ Proxy (HBoolEQ sel (KMember n ns)), Apply (ch, FHUProj sel ns) (HList (e ': l), Proxy n)) => Apply (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: FHUProj sel ns -> (HList (e ': l), Proxy n) -> ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (FHUProj sel ns) (HList l, Proxy ('HSucc n)) => Apply (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'False, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'True, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

(HNats2Integrals ns, HNat2Integral n) => HNats2Integrals (n ': ns) Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hNats2Integrals :: Integral i => Proxy (n ': ns) -> [i] Source #

(HNat2Integral n, HLookupByHNatR n u ~ le, le ~ Tagged l e, IArray UArray e, e ~ GetElemTy u) => HLookupByHNatUS1 ('Left t :: Either HNat HNat) n u us le Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByHNatUS1 :: Proxy ('Left t) -> Proxy n -> RecordU u -> HList us -> le Source #

HLookupByHNatUS t us e => HLookupByHNatUS1 ('Right t :: Either HNat HNat) n u us e Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByHNatUS1 :: Proxy ('Right t) -> Proxy n -> RecordU u -> HList us -> e Source #

type KMember n ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.HArray

type KMember n ('[] :: [HNat]) = 'False
type KMember n (n1 ': l) Source # 
Instance details

Defined in Data.HList.HArray

type KMember n (n1 ': l) = HOr (HNatEq n n1) (KMember n l)
type ApplyR (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (Proxy (HBoolEQ sel (KMember n ns)), FHUProj sel ns) (HList (e ': l), Proxy n)
type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (FHUProj sel ns) (HList l, Proxy ('HSucc n))
type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) = HJust (e, (HList l, Proxy ('HSucc n)))
type HNats (Proxy n ': l) Source # 
Instance details

Defined in Data.HList.HList

type HNats (Proxy n ': l) = n ': HNats l

type family HBoolEQ (t1 :: Bool) (t2 :: Bool) :: Bool Source #

Instances

Instances details
type HBoolEQ 'False 'False Source # 
Instance details

Defined in Data.HList.FakePrelude

type HBoolEQ 'False 'True Source # 
Instance details

Defined in Data.HList.FakePrelude

type HBoolEQ 'True 'False Source # 
Instance details

Defined in Data.HList.FakePrelude

type HBoolEQ 'True 'True Source # 
Instance details

Defined in Data.HList.FakePrelude

type HBoolEQ 'True 'True = 'True

class HCond (t :: Bool) x y z | t x y -> z where Source #

Methods

hCond :: Proxy t -> x -> y -> z Source #

Instances

Instances details
HCond 'False x y y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hCond :: Proxy 'False -> x -> y -> y Source #

HCond 'True x y x Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

hCond :: Proxy 'True -> x -> y -> x Source #

class HNotFD (b :: Bool) (nb :: Bool) | b -> nb, nb -> b Source #

as compared with HNot this version is injective

Instances

Instances details
HNotFD 'False 'True Source # 
Instance details

Defined in Data.HList.FakePrelude

HNotFD 'True 'False Source # 
Instance details

Defined in Data.HList.FakePrelude

type family HNot (x :: Bool) :: Bool Source #

Instances

Instances details
type HNot 'False Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNot 'False = 'True
type HNot 'True Source # 
Instance details

Defined in Data.HList.FakePrelude

type HNot 'True = 'False

type family HOr (t1 :: Bool) (t2 :: Bool) :: Bool Source #

Instances

Instances details
type HOr 'False t Source # 
Instance details

Defined in Data.HList.FakePrelude

type HOr 'False t = t
type HOr 'True t Source # 
Instance details

Defined in Data.HList.FakePrelude

type HOr 'True t = 'True

type family HAnd (t1 :: Bool) (t2 :: Bool) :: Bool Source #

Instances

Instances details
type HAnd 'False t Source # 
Instance details

Defined in Data.HList.FakePrelude

type HAnd 'False t = 'False
type HAnd 'True t Source # 
Instance details

Defined in Data.HList.FakePrelude

type HAnd 'True t = t

class ShowLabel l where Source #

Methods

showLabel :: Label l -> String Source #

Instances

Instances details
KnownNat x => ShowLabel (x :: Nat) Source # 
Instance details

Defined in Data.HList.Label6

Methods

showLabel :: Label x -> String Source #

KnownSymbol x => ShowLabel (x :: Symbol) Source # 
Instance details

Defined in Data.HList.Label6

Methods

showLabel :: Label x -> String Source #

Typeable x => ShowLabel (x :: Type) Source #

Equality on labels

Show label

Instance details

Defined in Data.HList.Label5

Methods

showLabel :: Label x -> String Source #

Show desc => ShowLabel (Lbl x ns desc :: Type) Source #

Equality on labels (descriptions are ignored) Use generic instance

Show label

Instance details

Defined in Data.HList.Label3

Methods

showLabel :: Label (Lbl x ns desc) -> String Source #

data Label l Source #

A special Proxy for record labels, polykinded

Constructors

Label 

Instances

Instances details
HEqBy HLeFn x y b => HEqBy HLeFn (Label x :: Type) (Label y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

Label t ~ Label t' => SameLabels (Label t :: Type) (t' :: Symbol) Source # 
Instance details

Defined in Data.HList.FakePrelude

Label t ~ Label t' => SameLabels (Label t :: Type) (Label t' :: Type) Source # 
Instance details

Defined in Data.HList.FakePrelude

Label t ~ Label (Lbl ix ns n) => SameLabels (Label t :: Type) (Lbl ix ns n :: Type) Source # 
Instance details

Defined in Data.HList.Label3

Label t ~ Label t' => SameLabels (Label t :: Type) (Tagged t' a :: Type) Source # 
Instance details

Defined in Data.HList.FakePrelude

(HasField l (Record r) u, HasFieldPath needJust ls u v) => HasFieldPath needJust (Label l ': ls) (Record r) v Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Record r -> v Source #

(HasField l (Variant r) (Maybe u), HasFieldPath 'True ls u (Maybe v)) => HasFieldPath needJust (Label l ': ls) (Variant r) (Maybe v) Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Variant r -> Maybe v Source #

(lv ~ Tagged l v, HUnzip (Proxy :: [Type] -> Type) ls vs lvs) => HUnzip (Proxy :: [Type] -> Type) (Label l ': ls) (v ': vs) (lv ': lvs) Source # 
Instance details

Defined in Data.HList.HListPrelude

Methods

hUnzip :: Proxy (lv ': lvs) -> (Proxy (Label l ': ls), Proxy (v ': vs)) Source #

Show desc => Show (Label (Lbl x ns desc)) Source # 
Instance details

Defined in Data.HList.Label3

Methods

showsPrec :: Int -> Label (Lbl x ns desc) -> ShowS #

show :: Label (Lbl x ns desc) -> String #

showList :: [Label (Lbl x ns desc)] -> ShowS #

IsKeyFN (Label s -> a -> b) 'True Source #

labels that impose no restriction on the type of the (single) argument which follows

>>> let testF (_ :: Label "a") (a :: Int) () = a+1
>>> kw (hBuild testF) (Label :: Label "a") 5 ()
6
Instance details

Defined in Data.HList.Keyword

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #
>>> let labelX = Label :: Label "x"
>>> let labelY = Label :: Label "y"
>>> let p = labelX .*. labelY .*. emptyProxy
>>> :t p
p :: Proxy '["x", "y"]
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let s = label6 .*. label3 .*. emptyProxy
>>> :t s
s :: Proxy '[Label "6", Label (Lbl 'HZero () ())]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (x ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (Lbl n' ns' desc' ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

HExtend (Label x) (Proxy ('[] :: [Type])) Source #

to keep types shorter, .*. used with Proxy avoids producing a Proxy :: Proxy '[Label x,Label y,Label z] if Proxy :: Proxy '[x,y,z] is not a kind error (as it is when mixing Label6 and Label3 labels).

ghc-7.6 does not accept Proxy ('[] :: [k]) so for now require k ~ *

Instance details

Defined in Data.HList.HListPrelude

Associated Types

type HExtendR (Label x) (Proxy '[]) Source #

Methods

(.*.) :: Label x -> Proxy '[] -> HExtendR (Label x) (Proxy '[]) Source #

EnsureLabel (Label x) (Label x) Source # 
Instance details

Defined in Data.HList.Labelable

Methods

toLabel :: Label x -> Label x Source #

EnsureLabel (Proxy x) (Label x) Source # 
Instance details

Defined in Data.HList.Labelable

Methods

toLabel :: Proxy x -> Label x Source #

ToSym (a b c) x => EnsureLabel (a b c) (Label x) Source #

get the Label out of a LabeledTo (ie. `foobar when using HListPP).

Instance details

Defined in Data.HList.Labelable

Methods

toLabel :: a b c -> Label x Source #

(Labelable x r s t a b, j ~ p a (f b), k2 ~ p (r s) (f (r t)), ty ~ LabelableTy r, LabeledOpticP ty p, LabeledOpticF ty f, LabeledOpticTo ty x (->), LabelablePath xs i j) => LabelablePath (Label x ': xs) i k2 Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLens'Path :: Label (Label x ': xs) -> i -> k2 Source #

type UnLabel (proxy :: a) (Label x ': xs) Source # 
Instance details

Defined in Data.HList.Record

type UnLabel (proxy :: a) (Label x ': xs) = x ': UnLabel proxy xs
type ZipTagged (Label t ': ts :: [Type]) (v ': vs) Source # 
Instance details

Defined in Data.HList.FakePrelude

type ZipTagged (Label t ': ts :: [Type]) (v ': vs) = Tagged t v ': ZipTagged ts vs
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (y ': (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (y ': (x ': xs))
type HExtendR (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label y) (Proxy (x ': xs)) = Proxy (Label y ': MapLabel (x ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) = Proxy (Label (Lbl n ns desc) ': MapLabel (x ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) = Proxy (Lbl n ns desc ': (Lbl n' ns' desc' ': xs))
type HExtendR (Label x) (Proxy ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HListPrelude

type HExtendR (Label x) (Proxy ('[] :: [Type])) = Proxy '[x]
type LabelsOf (Label l ': r) Source # 
Instance details

Defined in Data.HList.Record

type LabelsOf (Label l ': r) = Label l ': LabelsOf r

data HUntag Source #

Constructors

HUntag 

Instances

Instances details
Tagged t x ~ tx => ApplyAB HUntag tx x Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HUntag -> tx -> x Source #

newtype LiftA2 f Source #

Constructors

LiftA2 f 

Instances

Instances details
(ApplyAB f (x, y) z, mz ~ m z, mxy ~ (m x, m y), Applicative m) => ApplyAB (LiftA2 f) mxy mz Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: LiftA2 f -> mxy -> mz Source #

newtype HFmap f Source #

Constructors

HFmap f 

Instances

Instances details
(x ~ t a, y ~ t b, Functor t, ApplyAB f a b) => ApplyAB (HFmap f) x y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HFmap f -> x -> y Source #

data HFlip Source #

Constructors

HFlip 

Instances

Instances details
(f1 ~ (a -> b -> c), f2 ~ (b -> a -> c)) => ApplyAB HFlip f1 f2 Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HFlip -> f1 -> f2 Source #

newtype HSeq x Source #

((a,b) -> f a >> b)

Constructors

HSeq x 

Instances

Instances details
(Monad m, ApplyAB f x fx, fx ~ m (), pair ~ (x, m ()), ApplyAB f x (m ())) => ApplyAB (HSeq f) pair fx Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HSeq f -> pair -> fx Source #

data Comp Source #

app Comp (f,g) = g . f. Works like:

>>> applyAB Comp (succ, pred) 'a'
'a'
>>> applyAB Comp (toEnum :: Int -> Char, fromEnum) 10
10

Note that defaulting will sometimes give you the wrong thing

used to work (with associated types calculating result/argument types)
>>> applyAB Comp (fromEnum, toEnum) 'a'
*** Exception: Prelude.Enum.().toEnum: bad argument

Constructors

Comp 

Instances

Instances details
(y ~ y', fg ~ (x -> y, y' -> z), r ~ (x -> z)) => ApplyAB Comp fg r Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Comp -> fg -> r Source #

data HComp g f Source #

Compose two instances of ApplyAB

>>> applyAB (HComp HRead HShow) (5::Double) :: Double
5.0

Constructors

HComp g f
g . f

Instances

Instances details
(ApplyAB f a b, ApplyAB g b c) => ApplyAB (HComp g f) a c Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HComp g f -> a -> c Source #

data HShow Source #

show

Constructors

HShow 

Instances

Instances details
(String ~ string, Show a) => ApplyAB HShow a string Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HShow -> a -> string Source #

data HRead Source #

read

>>> applyAB HRead "5.0" :: Double
5.0

Constructors

HRead 

Instances

Instances details
(String ~ string, Read a) => ApplyAB HRead string a Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HRead -> string -> a Source #

data HPrint Source #

print. An alternative implementation could be:

>>> let hPrint = Fun print :: Fun Show (IO ())

This produces:

>>> :t applyAB hPrint
applyAB hPrint :: Show a => a -> IO ()

Constructors

HPrint 

Instances

Instances details
(io ~ IO (), Show x) => ApplyAB HPrint x io Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HPrint -> x -> io Source #

type family FunCxt (cxts :: k) a :: Constraint Source #

Instances

Instances details
type FunCxt (cxt :: ()) a Source #

should there be so many ways to write no constraint?

Instance details

Defined in Data.HList.FakePrelude

type FunCxt (cxt :: ()) a = ()
type FunCxt (cxt :: Type) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunCxt (cxt :: Type) a = cxt ~ a
type FunCxt ('[] :: [k]) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunCxt ('[] :: [k]) a = ()
type FunCxt (x ': xs :: [Type -> Constraint]) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunCxt (x ': xs :: [Type -> Constraint]) a = (x a, FunCxt xs a)
type FunCxt (cxt :: Type -> Constraint) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunCxt (cxt :: Type -> Constraint) a = cxt a

type family FunApp (fns :: k) a Source #

Instances

Instances details
type FunApp (fn :: ()) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunApp (fn :: ()) a = a
type FunApp (fn :: Type) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunApp (fn :: Type) a = fn
type FunApp (fn :: Type -> Type) a Source # 
Instance details

Defined in Data.HList.FakePrelude

type FunApp (fn :: Type -> Type) a = fn a

data Fun' (cxt :: k1) (geta :: k2) Source #

see Fun. The only difference here is that the argument type is calculated from the result type.

>>> let rd = Fun' read :: Fun' Read String
>>> :t applyAB rd
applyAB rd :: Read b => [Char] -> b
>>> let fromJust' = Fun' (\(Just a) -> a) :: Fun' '[] Maybe
>>> :t applyAB fromJust'
applyAB fromJust' :: Maybe b -> b

Note this use of Fun' means we don't have to get the b out of Maybe b,

Constructors

Fun' (forall b. FunCxt cxt b => FunApp geta b -> b) 

Instances

Instances details
(FunCxt cxt b, FunApp geta b ~ a) => ApplyAB (Fun' cxt geta) a b Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Fun' cxt geta -> a -> b Source #

data Fun (cxt :: k1) (getb :: k2) Source #

Constructors

Fun (forall a. FunCxt cxt a => a -> FunApp getb a) 

Instances

Instances details
(FunCxt cxt a, FunApp getb a ~ b) => ApplyAB (Fun cxt getb) a b Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Fun cxt getb -> a -> b Source #

class ApplyAB f a b where Source #

No constraints on result and argument types

Methods

applyAB :: f -> a -> b Source #

Instances

Instances details
(y ~ y', fg ~ (x -> y, y' -> z), r ~ (x -> z)) => ApplyAB Comp fg r Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Comp -> fg -> r Source #

(f1 ~ (a -> b -> c), f2 ~ (b -> a -> c)) => ApplyAB HFlip f1 f2 Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HFlip -> f1 -> f2 Source #

(io ~ IO (), Show x) => ApplyAB HPrint x io Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HPrint -> x -> io Source #

(String ~ string, Read a) => ApplyAB HRead string a Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HRead -> string -> a Source #

(String ~ string, Show a) => ApplyAB HShow a string Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HShow -> a -> string Source #

Tagged t x ~ tx => ApplyAB HUntag tx x Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HUntag -> tx -> x Source #

(x ~ Proxy y, Monoid y) => ApplyAB ConstMempty x y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: ConstMempty -> x -> y Source #

(x ~ (e, HList l), y ~ HList (e ': l)) => ApplyAB FHCons x y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: FHCons -> x -> y Source #

hJustA ~ HJust a => ApplyAB HFromJust hJustA a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HFromJust -> hJustA -> a Source #

(aa ~ (a, a), Monoid a) => ApplyAB UncurryMappend aa a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: UncurryMappend -> aa -> a Source #

(aa ~ (a, a), Semigroup a) => ApplyAB UncurrySappend aa a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: UncurrySappend -> aa -> a Source #

(HZip3 a b c, x ~ (HList a, HList b), y ~ HList c) => ApplyAB HZipF x y Source # 
Instance details

Defined in Data.HList.HZip

Methods

applyAB :: HZipF -> x -> y Source #

(x ~ Tagged l v, y ~ HList '[Label l, v]) => ApplyAB TaggedToKW x y Source # 
Instance details

Defined in Data.HList.Keyword

Methods

applyAB :: TaggedToKW -> x -> y Source #

tx ~ Tagged t x => ApplyAB TaggedFn x tx Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: TaggedFn -> x -> tx Source #

(ux ~ RecordU x, hx ~ HList x, RecordUToRecord x) => ApplyAB BoxF ux hx Source # 
Instance details

Defined in Data.HList.RecordU

Methods

applyAB :: BoxF -> ux -> hx Source #

(hx ~ HList x, ux ~ RecordU x, RecordToRecordU x) => ApplyAB UnboxF hx ux Source # 
Instance details

Defined in Data.HList.RecordU

Methods

applyAB :: UnboxF -> hx -> ux Source #

y ~ Tagged t (Maybe e) => ApplyAB ConstTaggedNothing x y Source # 
Instance details

Defined in Data.HList.Variant

Methods

applyAB :: ConstTaggedNothing -> x -> y Source #

(mx ~ Maybe x, my ~ Maybe y, HCast y x) => ApplyAB HCastF mx my Source # 
Instance details

Defined in Data.HList.Variant

Methods

applyAB :: HCastF -> mx -> my Source #

(x ~ (Tagged t (Maybe e), [Variant v]), y ~ [Variant (Tagged t e ': v)], MkVariant t e (Tagged t e ': v)) => ApplyAB HMaybiedToVariantFs x y Source # 
Instance details

Defined in Data.HList.Variant

Methods

applyAB :: HMaybiedToVariantFs -> x -> y Source #

(ee ~ (e, e), Eq e, bool ~ Bool) => ApplyAB UncurryEq ee bool Source # 
Instance details

Defined in Data.HList.Variant

Methods

applyAB :: UncurryEq -> ee -> bool Source #

e' ~ e => ApplyAB HRmTag (e, t) e' Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HRmTag -> (e, t) -> e' Source #

(y ~ ReadP x, Read x) => ApplyAB ReadElement (Proxy x) y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: ReadElement -> Proxy x -> y Source #

(Read v, ShowLabel l, x ~ Tagged l v, ReadP x ~ y) => ApplyAB ReadComponent (Proxy x) y Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: ReadComponent -> Proxy x -> y Source #

(Data d, (c (d -> b), d) ~ x, c b ~ y) => ApplyAB (GfoldlK c) x y Source # 
Instance details

Defined in Data.HList.Data

Methods

applyAB :: GfoldlK c -> x -> y Source #

(Data b, x ~ (t, c (b -> r)), y ~ c r) => ApplyAB (GunfoldK c) x y Source # 
Instance details

Defined in Data.HList.Data

Methods

applyAB :: GunfoldK c -> x -> y Source #

(x ~ t a, y ~ t b, Functor t, ApplyAB f a b) => ApplyAB (HFmap f) x y Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HFmap f -> x -> y Source #

hJustA ~ HJust a => ApplyAB (HJust t) a hJustA Source #

HJust () is a placeholder for a function that applies the HJust constructor

Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HJust t -> a -> hJustA Source #

(Monad m, ApplyAB f x fx, fx ~ m (), pair ~ (x, m ()), ApplyAB f x (m ())) => ApplyAB (HSeq f) pair fx Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HSeq f -> pair -> fx Source #

(ApplyAB f (x, y) z, mz ~ m z, mxy ~ (m x, m y), Applicative m) => ApplyAB (LiftA2 f) mxy mz Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: LiftA2 f -> mxy -> mz Source #

(hxs ~ HList xs, hxxs ~ HList (x ': xs)) => ApplyAB (FHCons2 x) hxs hxxs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: FHCons2 x -> hxs -> hxxs Source #

et ~ (e, t) => ApplyAB (HAddTag t) e et Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HAddTag t -> e -> et Source #

(HMapCxt r f a b, as ~ r a, bs ~ r b) => ApplyAB (HMap f) as bs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HMap f -> as -> bs Source #

(HMapCxt HList f a b, as ~ HList a, bs ~ HList b) => ApplyAB (HMapL f) as bs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HMapL f -> as -> bs Source #

(l ~ [e'], ApplyAB f e e', el ~ (e, l)) => ApplyAB (Mapcar f) el l Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: Mapcar f -> el -> l Source #

(HMapCxt Record f x y, rx ~ Record x, ry ~ Record y) => ApplyAB (HMapR f) rx ry Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: HMapR f -> rx -> ry Source #

(vx ~ Variant x, vy ~ Variant y, HMapAux Variant (HFmap f) x y, SameLength x y) => ApplyAB (HMapV f) vx vy Source #

apply a function to all values that could be in the variant.

Instance details

Defined in Data.HList.Variant

Methods

applyAB :: HMapV f -> vx -> vy Source #

ApplyAB f e e' => ApplyAB (MapCar f) (e, HList l) (HList (e' ': l)) Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: MapCar f -> (e, HList l) -> HList (e' ': l) Source #

(ApplyAB f a b, ApplyAB g b c) => ApplyAB (HComp g f) a c Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: HComp g f -> a -> c Source #

(x' ~ x, y' ~ y) => ApplyAB (x' -> y') x y Source #

note this function will only be available at a single type (that is, hMap succ will only work on HList that contain only one type)

Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: (x' -> y') -> x -> y Source #

(FunCxt cxt a, FunApp getb a ~ b) => ApplyAB (Fun cxt getb) a b Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Fun cxt getb -> a -> b Source #

(FunCxt cxt b, FunApp geta b ~ a) => ApplyAB (Fun' cxt geta) a b Source # 
Instance details

Defined in Data.HList.FakePrelude

Methods

applyAB :: Fun' cxt geta -> a -> b Source #

class Apply f a where Source #

simpler/weaker version where type information only propagates forward with this one. applyAB defined below, is more complicated / verbose to define, but it offers better type inference. Most uses have been converted to applyAB, so there is not much that can be done with Apply.

Associated Types

type ApplyR f a :: * Source #

Methods

apply :: f -> a -> ApplyR f a Source #

Instances

Instances details
HLookupByHNat n l => Apply (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHLookupByHNat l) (Proxy n) Source #

(ch ~ Proxy (HBoolEQ sel (KMember n ns)), Apply (ch, FHUProj sel ns) (HList (e ': l), Proxy n)) => Apply (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: FHUProj sel ns -> (HList (e ': l), Proxy n) -> ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (FHUProj sel ns) (HList ('[] :: [Type]), n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList '[], n) Source #

Methods

apply :: FHUProj sel ns -> (HList '[], n) -> ApplyR (FHUProj sel ns) (HList '[], n) Source #

Apply (FHUProj sel ns) (HList l, Proxy ('HSucc n)) => Apply (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'False, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'True, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

hAnd :: Proxy t1 -> Proxy t2 -> Proxy (HAnd t1 t2) Source #

demote to values

hOr :: Proxy t1 -> Proxy t2 -> Proxy (HOr t1 t2) Source #

demote to values

hNot :: HNotFD a notA => Proxy a -> Proxy notA Source #

hSucc :: Proxy (n :: HNat) -> Proxy (HSucc n) Source #

hLt :: Proxy x -> Proxy y -> Proxy (HLt x y) Source #

hLe :: Proxy x -> Proxy y -> Proxy (HLe x y) Source #

hEq :: HEq x y b => x -> y -> Proxy b Source #

asLengthOf :: SameLength x y => r x -> s y -> r x Source #

sameLabels :: SameLabels x y => p (r x) (f (q y)) -> p (r x) (f (q y)) Source #

sameLabels constrains the type of an optic, such that the labels (t in Tagged t a) are the same. x or y may have more elements than the other, in which case the elements at the end of the longer list do not have their labels constrained.

see also sameLength

class HUnzip r x y xy => HZip (r :: [*] -> *) x y xy where Source #

zip. Variant supports hUnzip, but not hZip (hZipVariant returns a Maybe)

Methods

hZip :: r x -> r y -> r xy Source #

Instances

Instances details
(SameLengths '[x, y, xy], HZipList x y xy) => HZip HList x y xy Source # 
Instance details

Defined in Data.HList.HList

Methods

hZip :: HList x -> HList y -> HList xy Source #

(HZipRecord x y xy, SameLengths '[x, y, xy]) => HZip Record x y xy Source #
>>> let x :: Record '[Tagged "x" Int]; x = undefined
>>> let y :: Record '[Tagged "x" Char]; y = undefined
>>> :t hZip x y
hZip x y :: Record '[Tagged "x" (Int, Char)]
Instance details

Defined in Data.HList.Record

Methods

hZip :: Record x -> Record y -> Record xy Source #

(HUnzip TIP x y xy, HZipList xL yL xyL, lty ~ (HList xL -> HList yL -> HList xyL), Coercible lty (TIP x -> TIP y -> TIP xy), UntagR x ~ xL, UntagR y ~ yL, UntagR xy ~ xyL, UntagTag x, UntagTag y, UntagTag xy) => HZip TIP x y xy Source # 
Instance details

Defined in Data.HList.TIP

Methods

hZip :: TIP x -> TIP y -> TIP xy Source #

HUnzip (Proxy :: [Type] -> Type) ls vs lvs => HZip (Proxy :: [Type] -> Type) ls vs lvs Source #

Missing from GHC-7.6.3 due to a bug:

let r = hEnd $ hBuild 1 2 3
*Data.HList> hZipList r r
H[(1,1),(2,2),(3,3)]
*Data.HList> hZip r r

<interactive>:30:1:
    Couldn't match type `Label k l' with `Integer'
    When using functional dependencies to combine
      HUnzip
        (Proxy [*]) ((':) * (Label k l) ls) ((':) * v vs) ((':) * lv lvs),
        arising from the dependency `xy -> x y'
        in the instance declaration at Data/HList/HListPrelude.hs:96:10
      HUnzip
        HList
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':) * Integer ((':) * Integer ((':) * Integer ('[] *))))
        ((':)
           *
           (Integer, Integer)
           ((':) * (Integer, Integer) ((':) * (Integer, Integer) ('[] *)))),
        arising from a use of `hZip' at <interactive>:30:1-4
    In the expression: hZip r r
    In an equation for `it': it = hZip r r
Instance details

Defined in Data.HList.HListPrelude

Methods

hZip :: Proxy ls -> Proxy vs -> Proxy lvs Source #

class SameLengths [x, y, xy] => HUnzip (r :: [*] -> *) x y xy | x y -> xy, xy -> x y where Source #

Methods

hUnzip :: r xy -> (r x, r y) Source #

Instances

Instances details
(SameLengths '[x, y, xy], HZipList x y xy) => HUnzip HList x y xy Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnzip :: HList xy -> (HList x, HList y) Source #

(HZipRecord x y xy, SameLengths '[x, y, xy]) => HUnzip Record x y xy Source # 
Instance details

Defined in Data.HList.Record

Methods

hUnzip :: Record xy -> (Record x, Record y) Source #

(HZipList xL yL xyL, lty ~ (HList xyL -> (HList xL, HList yL)), Coercible lty (TIP xy -> (TIP x, TIP y)), UntagR x ~ xL, TagR xL ~ x, UntagR y ~ yL, TagR yL ~ y, UntagR xy ~ xyL, TagR xyL ~ xy, SameLengths '[x, y, xy], UntagTag x, UntagTag y, UntagTag xy) => HUnzip TIP x y xy Source # 
Instance details

Defined in Data.HList.TIP

Methods

hUnzip :: TIP xy -> (TIP x, TIP y) Source #

(HUnzip Variant (x2 ': xs) (y2 ': ys) (xy2 ': xys), SameLength xs ys, SameLength ys xys, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant (tx ': (x2 ': xs)) (ty ': (y2 ': ys)) (txy ': (xy2 ': xys)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hUnzip :: Variant (txy ': (xy2 ': xys)) -> (Variant (tx ': (x2 ': xs)), Variant (ty ': (y2 ': ys))) Source #

(Unvariant '[txy] txy, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant '[tx] '[ty] '[txy] Source # 
Instance details

Defined in Data.HList.Variant

Methods

hUnzip :: Variant '[txy] -> (Variant '[tx], Variant '[ty]) Source #

HUnzip (Proxy :: [Type] -> Type) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HListPrelude

Methods

hUnzip :: Proxy '[] -> (Proxy '[], Proxy '[]) Source #

(lv ~ Tagged l v, HUnzip (Proxy :: [Type] -> Type) ls vs lvs) => HUnzip (Proxy :: [Type] -> Type) (Label l ': ls) (v ': vs) (lv ': lvs) Source # 
Instance details

Defined in Data.HList.HListPrelude

Methods

hUnzip :: Proxy (lv ': lvs) -> (Proxy (Label l ': ls), Proxy (v ': vs)) Source #

class HDeleteAtLabel (r :: [*] -> *) (l :: k) v v' | l v -> v' where Source #

Methods

hDeleteAtLabel :: Label l -> r v -> r v' Source #

Instances

Instances details
(HDeleteAtHNat n l, HType2HNat e l n, l' ~ HDeleteAtHNatR n l) => HDeleteAtLabel HList (e :: Type) l l' Source #

should this instead delete the first element of that type?

Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteAtLabel :: Label e -> HList l -> HList l' Source #

H2ProjectByLabels '[Label l] v t1 v' => HDeleteAtLabel Record (l :: k) v v' Source # 
Instance details

Defined in Data.HList.Record

Methods

hDeleteAtLabel :: Label l -> Record v -> Record v' Source #

(HDeleteAtLabel Record e v v', HTypeIndexed v') => HDeleteAtLabel TIP (e :: k) v v' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hDeleteAtLabel :: Label e -> TIP v -> TIP v' Source #

class HTypes2HNats es l (ns :: [HNat]) | es l -> ns Source #

Instances

Instances details
HTypes2HNats ('[] :: [Type]) (l :: [Type]) ('[] :: [HNat]) Source #

And lift to the list of types

Instance details

Defined in Data.HList.HTypeIndexed

(HType2HNat e l n, HTypes2HNats es l ns) => HTypes2HNats (e ': es :: [Type]) (l :: [Type]) (n ': ns) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

class HType2HNat (e :: k) (l :: [k]) (n :: HNat) | e l -> n Source #

Map a type (key) to a natural (index) within the collection This is a purely type-level computation

Instances

Instances details
(HEq e1 e b, HType2HNatCase b e1 l n) => HType2HNat (e1 :: Type) (e ': l :: [Type]) n Source #

Map a type to a natural (index within the collection) This is a purely type-level computation

Instance details

Defined in Data.HList.HTypeIndexed

class HProject l l' where Source #

Methods

hProject :: l -> l' Source #

Instances

Instances details
(HOccurs e l, HProject l (HList l')) => HProject l (HList (e ': l')) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hProject :: l -> HList (e ': l') Source #

HProject (HList l) (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hProject :: HList l -> HList '[] Source #

class HOccursNot (e :: k) (l :: [k]) Source #

Instances

Instances details
HOccursNot1 e xs xs => HOccursNot (e :: k) (xs :: [k]) Source # 
Instance details

Defined in Data.HList.HOccurs

class HOccurs e l where Source #

Methods

hOccurs :: l -> e Source #

Instances

Instances details
(HOccurrence e (x ': y) l', HOccurs' e l' (x ': y)) => HOccurs e (HList (x ': y)) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs :: HList (x ': y) -> e Source #

tee ~ Tagged e e => HOccurs e (TIP '[tee]) Source #

One occurrence and nothing is left

This variation provides an extra feature for singleton lists. That is, the result type is unified with the element in the list. Hence the explicit provision of a result type can be omitted.

Instance details

Defined in Data.HList.TIP

Methods

hOccurs :: TIP '[tee] -> e Source #

HasField e (Record (x ': (y ': l))) e => HOccurs e (TIP (x ': (y ': l))) Source # 
Instance details

Defined in Data.HList.TIP

Methods

hOccurs :: TIP (x ': (y ': l)) -> e Source #

(HasField o (TIC l) mo, mo ~ Maybe o) => HOccurs mo (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

hOccurs :: TIC l -> mo Source #

type family HAppendR (l1 :: k) (l2 :: k) :: k Source #

poly-kinded, but hAppend only works in cases where the kind variable k is *

Instances

Instances details
type HAppendR (HList l1 :: Type) (HList l2 :: Type) Source # 
Instance details

Defined in Data.HList.HList

type HAppendR (HList l1 :: Type) (HList l2 :: Type) = HList (HAppendListR l1 l2)
type HAppendR (Record r1 :: Type) (Record r2 :: Type) Source # 
Instance details

Defined in Data.HList.Record

type HAppendR (Record r1 :: Type) (Record r2 :: Type) = Record (HAppendListR r1 r2)
type HAppendR (TIP l :: Type) (TIP l' :: Type) Source # 
Instance details

Defined in Data.HList.TIP

type HAppendR (TIP l :: Type) (TIP l' :: Type) = TIP (HAppendListR l l')

class HAppend l1 l2 where Source #

Methods

hAppend :: l1 -> l2 -> HAppendR l1 l2 Source #

Instances

Instances details
HAppendList l1 l2 => HAppend (HList l1) (HList l2) Source # 
Instance details

Defined in Data.HList.HList

Methods

hAppend :: HList l1 -> HList l2 -> HAppendR (HList l1) (HList l2) Source #

(HRLabelSet (HAppendListR r1 r2), HAppend (HList r1) (HList r2)) => HAppend (Record r1) (Record r2) Source #
(.*.)
Add a field to a record. Analagous to (++) for lists.
record .*. field1
       .*. field2
Instance details

Defined in Data.HList.Record

Methods

hAppend :: Record r1 -> Record r2 -> HAppendR (Record r1) (Record r2) Source #

(HAppend (HList l) (HList l'), HTypeIndexed (HAppendListR l l')) => HAppend (TIP l) (TIP l') Source # 
Instance details

Defined in Data.HList.TIP

Methods

hAppend :: TIP l -> TIP l' -> HAppendR (TIP l) (TIP l') Source #

class SubType l l' Source #

Instances

Instances details
H2ProjectByLabels (LabelsOf r2) r1 r2 rout => SubType (Record r1 :: Type) (Record r2 :: Type) Source #

Subtyping for records

Instance details

Defined in Data.HList.Record

SubType (TIP l :: Type) (TIP ('[] :: [Type])) Source #

Subtyping for TIPs

Instance details

Defined in Data.HList.TIP

(HOccurs e (TIP l1), SubType (TIP l1) (TIP l2)) => SubType (TIP l1 :: Type) (TIP (e ': l2) :: Type) Source # 
Instance details

Defined in Data.HList.TIP

class HExtend e l where Source #

Associated Types

type HExtendR e l Source #

Methods

(.*.) :: e -> l -> HExtendR e l infixr 2 Source #

Instances

Instances details
HExtend e (HList l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HExtendR e (HList l) Source #

Methods

(.*.) :: e -> HList l -> HExtendR e (HList l) Source #

(HRLabelSet (Tagged e e ': l), HTypeIndexed l) => HExtend e (TIP l) Source # 
Instance details

Defined in Data.HList.TIP

Associated Types

type HExtendR e (TIP l) Source #

Methods

(.*.) :: e -> TIP l -> HExtendR e (TIP l) Source #

(le ~ Tagged l (Maybe e), HOccursNot (Label l) (LabelsOf v)) => HExtend le (Variant v) Source #

Extension for Variants prefers the first value

(l .=. Nothing) .*. v = v
(l .=. Just e)  .*. _ = mkVariant l e Proxy
Instance details

Defined in Data.HList.Variant

Associated Types

type HExtendR le (Variant v) Source #

Methods

(.*.) :: le -> Variant v -> HExtendR le (Variant v) Source #

(me ~ Maybe e, HOccursNot (Tagged e e) l) => HExtend me (TIC l) Source #
Nothing .*. x = x
Just a .*. y = mkTIC a
Instance details

Defined in Data.HList.TIC

Associated Types

type HExtendR me (TIC l) Source #

Methods

(.*.) :: me -> TIC l -> HExtendR me (TIC l) Source #

HRLabelSet (t ': r) => HExtend t (Record r) Source # 
Instance details

Defined in Data.HList.Record

Associated Types

type HExtendR t (Record r) Source #

Methods

(.*.) :: t -> Record r -> HExtendR t (Record r) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #
>>> let labelX = Label :: Label "x"
>>> let labelY = Label :: Label "y"
>>> let p = labelX .*. labelY .*. emptyProxy
>>> :t p
p :: Proxy '["x", "y"]
Instance details

Defined in Data.HList.Label6

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label y) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let s = label6 .*. label3 .*. emptyProxy
>>> :t s
s :: Proxy '[Label "6", Label (Lbl 'HZero () ())]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label y) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label y -> Proxy (x ': xs) -> HExtendR (Label y) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (x ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (Lbl n' ns' desc' ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

HExtend (Label x) (Proxy ('[] :: [Type])) Source #

to keep types shorter, .*. used with Proxy avoids producing a Proxy :: Proxy '[Label x,Label y,Label z] if Proxy :: Proxy '[x,y,z] is not a kind error (as it is when mixing Label6 and Label3 labels).

ghc-7.6 does not accept Proxy ('[] :: [k]) so for now require k ~ *

Instance details

Defined in Data.HList.HListPrelude

Associated Types

type HExtendR (Label x) (Proxy '[]) Source #

Methods

(.*.) :: Label x -> Proxy '[] -> HExtendR (Label x) (Proxy '[]) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (x ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (x ': xs) -> HExtendR (to p q) (Proxy (x ': xs)) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

if the proxy has Data.HList.Label3.Lbl, then everything has to be wrapped in Label to make the kinds match up.

Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (Lbl n ns desc ': xs) -> HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy ('[] :: [Type])) Source #

Together with the instance below, this allows writing

makeLabelable "x y z"
p = x .*. y .*. z .*. emptyProxy

Or with HListPP

p = `x .*. `y .*. `z .*. emptyProxy

instead of

p = Proxy :: Proxy ["x","y","z"]
Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy '[]) Source #

Methods

(.*.) :: to p q -> Proxy '[] -> HExtendR (to p q) (Proxy '[]) Source #

emptyProxy :: Proxy ('[] :: [Type]) Source #

similar to emptyRecord, emptyTIP, emptyHList (actually called HNil), except emptyProxy is the rightmost argument to .*.

type family AddLabel (x :: k) :: * where ... Source #

Equations

AddLabel (Label x) = Label x 
AddLabel x = Label x 

data Lbl (x :: HNat) (ns :: *) (desc :: *) Source #

Instances

Instances details
(HEqBy HLeFn n m b, ns ~ ns') => HEqBy HLeFn (Lbl n ns desc :: Type) (Lbl m ns' desc' :: Type) b Source #

Data.HList.Label3 labels can only be compared if they belong to the same namespace.

Instance details

Defined in Data.HList.HSort

Label t ~ Label (Lbl ix ns n) => SameLabels (Label t :: Type) (Lbl ix ns n :: Type) Source # 
Instance details

Defined in Data.HList.Label3

Show desc => ShowLabel (Lbl x ns desc :: Type) Source #

Equality on labels (descriptions are ignored) Use generic instance

Show label

Instance details

Defined in Data.HList.Label3

Methods

showLabel :: Label (Lbl x ns desc) -> String Source #

Show desc => Show (Label (Lbl x ns desc)) Source # 
Instance details

Defined in Data.HList.Label3

Methods

showsPrec :: Int -> Label (Lbl x ns desc) -> ShowS #

show :: Label (Lbl x ns desc) -> String #

showList :: [Label (Lbl x ns desc)] -> ShowS #

HExtend (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Mixing two label kinds means we have to include Label:

>>> let r = label3 .*. label6 .*. emptyProxy
>>> :t r
r :: Proxy '[Label (Lbl 'HZero () ()), Label "6"]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (x ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source #

HExtend (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

If possible, Label is left off:

>>> let q = label3 .*. label3 .*. emptyProxy
>>> :t q
q :: Proxy '[Lbl 'HZero () (), Lbl 'HZero () ()]
Instance details

Defined in Data.HList.Label3

Associated Types

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

Methods

(.*.) :: Label (Lbl n ns desc) -> Proxy (Lbl n' ns' desc' ': xs) -> HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source #

(to ~ LabeledTo x, ToSym (to p q) x) => HExtend (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

if the proxy has Data.HList.Label3.Lbl, then everything has to be wrapped in Label to make the kinds match up.

Instance details

Defined in Data.HList.Labelable

Associated Types

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

Methods

(.*.) :: to p q -> Proxy (Lbl n ns desc ': xs) -> HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source #

type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) Source # 
Instance details

Defined in Data.HList.Label3

type ZipTagged (Lbl ix ns n ': ts :: [Type]) (v ': vs) = Tagged (Lbl ix ns n) v ': ZipTagged ts vs
type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (x ': xs)) = Proxy (Label (Lbl n ns desc) ': MapLabel (x ': xs))
type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) Source # 
Instance details

Defined in Data.HList.Label3

type HExtendR (Label (Lbl n ns desc)) (Proxy (Lbl n' ns' desc' ': xs)) = Proxy (Lbl n ns desc ': (Lbl n' ns' desc' ': xs))
type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs)) Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR (to p q) (Proxy (Lbl n ns desc ': xs))

firstLabel :: ns -> desc -> Label (Lbl HZero ns desc) Source #

Construct the first label

nextLabel :: Label (Lbl x ns desc) -> desc' -> Label (Lbl (HSucc x) ns desc') Source #

Construct the next label

class IsKeyFN (t :: *) (flag :: Bool) | t -> flag Source #

All our keywords must be registered

Instances

Instances details
'False ~ flag => IsKeyFN t flag Source #

overlapping/fallback case

Instance details

Defined in Data.HList.TypeEqO

IsKeyFN (Label s -> a -> b) 'True Source #

labels that impose no restriction on the type of the (single) argument which follows

>>> let testF (_ :: Label "a") (a :: Int) () = a+1
>>> kw (hBuild testF) (Label :: Label "a") 5 ()
6
Instance details

Defined in Data.HList.Keyword

r ~ (c -> b) => IsKeyFN (K s c -> r) 'True Source #

The purpose of this instance is to be able to use the same Symbol (type-level string) at different types. If they are supposed to be the same, then use Label instead of K

>>> let kA = K :: forall t. K "a" t
>>> let testF (K :: K "a" Int) a1 (K :: K "a" Integer) a2 () = a1-fromIntegral a2

therefore the following options works:

>>> kw (hBuild testF) kA (5 :: Int) kA (3 :: Integer) ()
2
>>> kw (hBuild testF) (K :: K "a" Integer) 3 (K :: K "a" Int) 5 ()
2

But you cannot leave off all Int or Integer annotations.

Instance details

Defined in Data.HList.Keyword

class TupleType (t :: *) (b :: Bool) | t -> b Source #

Instances

Instances details
TupleType () 'True Source # 
Instance details

Defined in Data.HList.TypeEqO

'False ~ b => TupleType x b Source # 
Instance details

Defined in Data.HList.TypeEqO

TupleType (x, y) 'True Source # 
Instance details

Defined in Data.HList.TypeEqO

TupleType (x, y, z) 'True Source # 
Instance details

Defined in Data.HList.TypeEqO

data UncurrySappend Source #

Constructors

UncurrySappend 

Instances

Instances details
(aa ~ (a, a), Semigroup a) => ApplyAB UncurrySappend aa a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: UncurrySappend -> aa -> a Source #

data UncurryMappend Source #

Constructors

UncurryMappend 

Instances

Instances details
(aa ~ (a, a), Monoid a) => ApplyAB UncurryMappend aa a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: UncurryMappend -> aa -> a Source #

data ConstMempty Source #

Constructors

ConstMempty 

Instances

Instances details
(x ~ Proxy y, Monoid y) => ApplyAB ConstMempty x y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: ConstMempty -> x -> y Source #

class HZipList x y l | x y -> l, l -> x y where Source #

Methods

hZipList :: HList x -> HList y -> HList l Source #

hUnzipList :: HList l -> (HList x, HList y) Source #

Instances

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

Defined in Data.HList.HList

Methods

hZipList :: HList '[] -> HList '[] -> HList '[] Source #

hUnzipList :: HList '[] -> (HList '[], HList '[]) Source #

((x, y) ~ z, HZipList xs ys zs) => HZipList (x ': xs) (y ': ys) (z ': zs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hZipList :: HList (x ': xs) -> HList (y ': ys) -> HList (z ': zs) Source #

hUnzipList :: HList (z ': zs) -> (HList (x ': xs), HList (y ': ys)) Source #

class HSpanEqBy2 (b :: Bool) (f :: t) (x :: *) (y :: *) (ys :: [*]) (i :: [*]) (o :: [*]) | b f x y ys -> i o where Source #

Methods

hSpanEqBy2 :: Proxy b -> Proxy f -> x -> y -> HList ys -> (HList i, HList o) Source #

Instances

Instances details
HSpanEqBy2 'False (f :: t) x y ys ('[] :: [Type]) (y ': ys) Source # 
Instance details

Defined in Data.HList.HList

Methods

hSpanEqBy2 :: Proxy 'False -> Proxy f -> x -> y -> HList ys -> (HList '[], HList (y ': ys)) Source #

HSpanEqBy1 f x zs i o => HSpanEqBy2 'True (f :: t) x y zs (y ': i) o Source # 
Instance details

Defined in Data.HList.HList

Methods

hSpanEqBy2 :: Proxy 'True -> Proxy f -> x -> y -> HList zs -> (HList (y ': i), HList o) Source #

class HSpanEqBy1 (f :: t) (x :: *) (y :: [*]) (i :: [*]) (o :: [*]) | f x y -> i o where Source #

Methods

hSpanEqBy1 :: Proxy f -> x -> HList y -> (HList i, HList o) Source #

Instances

Instances details
HSpanEqBy1 (f :: t) x ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hSpanEqBy1 :: Proxy f -> x -> HList '[] -> (HList '[], HList '[]) Source #

(HEqBy f x y b, HSpanEqBy2 b f x y ys i o) => HSpanEqBy1 (f :: t) x (y ': ys) i o Source # 
Instance details

Defined in Data.HList.HList

Methods

hSpanEqBy1 :: Proxy f -> x -> HList (y ': ys) -> (HList i, HList o) Source #

class HSpanEqBy (f :: t) (x :: *) (y :: [*]) (fst :: [*]) (snd :: [*]) | f x y -> fst snd, fst snd -> y where Source #

HSpanEq x y fst snd is analogous to (fst,snd) = span (== x) y

Methods

hSpanEqBy :: Proxy f -> x -> HList y -> (HList fst, HList snd) Source #

Instances

Instances details
(HSpanEqBy1 f x y fst snd, HAppendListR fst snd ~ y) => HSpanEqBy (f :: t) x y fst snd Source # 
Instance details

Defined in Data.HList.HList

Methods

hSpanEqBy :: Proxy f -> x -> HList y -> (HList fst, HList snd) Source #

class HGroupBy (f :: t) (as :: [*]) (gs :: [*]) | f as -> gs, gs -> as where Source #

HGroupBy f x y is analogous to y = groupBy f x

given that f is used by HEqBy

Methods

hGroupBy :: Proxy f -> HList as -> HList gs Source #

Instances

Instances details
HGroupBy (f :: t) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hGroupBy :: Proxy f -> HList '[] -> HList '[] Source #

(HSpanEqBy f a as fst snd, HGroupBy f snd gs) => HGroupBy (f :: t) (a ': as) (HList (a ': fst) ': gs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hGroupBy :: Proxy f -> HList (a ': as) -> HList (HList (a ': fst) ': gs) Source #

class HPartitionEq1 (b :: Bool) f x1 x xs xi xo | b f x1 x xs -> xi xo where Source #

Methods

hPartitionEq1 :: Proxy b -> Proxy f -> Proxy x1 -> x -> HList xs -> (HList xi, HList xo) Source #

Instances

Instances details
HPartitionEq f x1 xs xi xo => HPartitionEq1 'False (f :: k1) (x1 :: k2) x xs xi (x ': xo) Source # 
Instance details

Defined in Data.HList.HList

Methods

hPartitionEq1 :: Proxy 'False -> Proxy f -> Proxy x1 -> x -> HList xs -> (HList xi, HList (x ': xo)) Source #

HPartitionEq f x1 xs xi xo => HPartitionEq1 'True (f :: k1) (x1 :: k2) x xs (x ': xi) xo Source # 
Instance details

Defined in Data.HList.HList

Methods

hPartitionEq1 :: Proxy 'True -> Proxy f -> Proxy x1 -> x -> HList xs -> (HList (x ': xi), HList xo) Source #

class HPartitionEq f x1 xs xi xo | f x1 xs -> xi xo where Source #

HPartitionEq f x1 xs xi xo is analogous to

(xi,xo) = partition (f x1) xs

where f is a "function" passed in using it's instance of HEqBy

Methods

hPartitionEq :: Proxy f -> Proxy x1 -> HList xs -> (HList xi, HList xo) Source #

Instances

Instances details
HPartitionEq (f :: k1) (x1 :: k2) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hPartitionEq :: Proxy f -> Proxy x1 -> HList '[] -> (HList '[], HList '[]) Source #

(HEqBy f x1 x b, HPartitionEq1 b f x1 x xs xi xo) => HPartitionEq (f :: k) (x1 :: Type) (x ': xs) xi xo Source # 
Instance details

Defined in Data.HList.HList

Methods

hPartitionEq :: Proxy f -> Proxy x1 -> HList (x ': xs) -> (HList xi, HList xo) Source #

type family HMapTail (xxs :: [*]) :: [*] Source #

evidence to satisfy the fundeps in HInits

Instances

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

Defined in Data.HList.HList

type HMapTail ('[] :: [Type]) = '[] :: [Type]
type HMapTail (HList (a ': as) ': bs) Source # 
Instance details

Defined in Data.HList.HList

type HMapTail (HList (a ': as) ': bs) = HList as ': HMapTail bs

type family HMapCons (x :: *) (xxs :: [*]) :: [*] Source #

evidence to satisfy the fundeps in HInits

Instances

Instances details
type HMapCons x ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

type HMapCons x ('[] :: [Type]) = '[] :: [Type]
type HMapCons x (HList a ': b) Source # 
Instance details

Defined in Data.HList.HList

type HMapCons x (HList a ': b) = HList (x ': a) ': HMapCons x b

data FHCons2 x Source #

similar to FHCons

Constructors

FHCons2 x 

Instances

Instances details
(hxs ~ HList xs, hxxs ~ HList (x ': xs)) => ApplyAB (FHCons2 x) hxs hxxs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: FHCons2 x -> hxs -> hxxs Source #

class HInits1 a b | a -> b, b -> a where Source #

behaves like tail . inits

Methods

hInits1 :: HList a -> HList b Source #

Instances

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

Defined in Data.HList.HList

Methods

hInits1 :: HList '[] -> HList '[HList '[]] Source #

(HInits1 xs ys, HMapCxt HList (FHCons2 x) ys ys', HMapCons x ys ~ ys', HMapTail ys' ~ ys) => HInits1 (x ': xs) (HList '[x] ': ys') Source # 
Instance details

Defined in Data.HList.HList

Methods

hInits1 :: HList (x ': xs) -> HList (HList '[x] ': ys') Source #

class HInits a b | a -> b, b -> a where Source #

Methods

hInits :: HList a -> HList b Source #

Instances

Instances details
HInits1 a b => HInits a (HList ('[] :: [Type]) ': b) Source # 
Instance details

Defined in Data.HList.HList

Methods

hInits :: HList a -> HList (HList '[] ': b) Source #

class HTails a b | a -> b, b -> a where Source #

Methods

hTails :: HList a -> HList b Source #

Instances

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

Defined in Data.HList.HList

Methods

hTails :: HList '[] -> HList '[HList '[]] Source #

HTails xs ys => HTails (x ': xs) (HList (x ': xs) ': ys) Source # 
Instance details

Defined in Data.HList.HList

Methods

hTails :: HList (x ': xs) -> HList (HList (x ': xs) ': ys) Source #

class HTuple v t | v -> t, t -> v where Source #

Methods

hToTuple :: HList v -> t Source #

alternatively: hUncurry (,,,)

hFromTuple :: t -> HList v Source #

Instances

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

Defined in Data.HList.HList

Methods

hToTuple :: HList '[] -> () Source #

hFromTuple :: () -> HList '[] Source #

HTuple '[a, b] (a, b) Source # 
Instance details

Defined in Data.HList.HList

Methods

hToTuple :: HList '[a, b] -> (a, b) Source #

hFromTuple :: (a, b) -> HList '[a, b] Source #

HTuple '[a, b, c] (a, b, c) Source # 
Instance details

Defined in Data.HList.HList

Methods

hToTuple :: HList '[a, b, c] -> (a, b, c) Source #

hFromTuple :: (a, b, c) -> HList '[a, b, c] Source #

HTuple '[a, b, c, d] (a, b, c, d) Source # 
Instance details

Defined in Data.HList.HList

Methods

hToTuple :: HList '[a, b, c, d] -> (a, b, c, d) Source #

hFromTuple :: (a, b, c, d) -> HList '[a, b, c, d] Source #

HTuple '[a, b, c, d, e] (a, b, c, d, e) Source # 
Instance details

Defined in Data.HList.HList

Methods

hToTuple :: HList '[a, b, c, d, e] -> (a, b, c, d, e) Source #

hFromTuple :: (a, b, c, d, e) -> HList '[a, b, c, d, e] Source #

HTuple '[a, b, c, d, e, f] (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.HList.HList

Methods

hToTuple :: HList '[a, b, c, d, e, f] -> (a, b, c, d, e, f) Source #

hFromTuple :: (a, b, c, d, e, f) -> HList '[a, b, c, d, e, f] Source #

class HDrop (n :: HNat) xs ys | n xs -> ys where Source #

Methods

hDrop :: HLengthGe xs n => Proxy n -> HList xs -> HList ys Source #

Instances

Instances details
HDrop 'HZero xs xs Source # 
Instance details

Defined in Data.HList.HList

Methods

hDrop :: Proxy 'HZero -> HList xs -> HList xs Source #

(HLengthGe xs n, HDrop n xs ys) => HDrop ('HSucc n) (x ': xs) ys Source # 
Instance details

Defined in Data.HList.HList

Methods

hDrop :: Proxy ('HSucc n) -> HList (x ': xs) -> HList ys Source #

class HTake (n :: HNat) xs ys | n xs -> ys where Source #

Methods

hTake :: (HLengthEq ys n, HLengthGe xs n) => Proxy n -> HList xs -> HList ys Source #

Instances

Instances details
HTake 'HZero xs ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hTake :: Proxy 'HZero -> HList xs -> HList '[] Source #

(HLengthEq ys n, HLengthGe xs n, HTake n xs ys) => HTake ('HSucc n) (x ': xs) (x ': ys) Source # 
Instance details

Defined in Data.HList.HList

Methods

hTake :: Proxy ('HSucc n) -> HList (x ': xs) -> HList (x ': ys) Source #

class HStripPrefix xs xsys ys | xs xsys -> ys Source #

analog of stripPrefix

Instances

Instances details
HStripPrefix ('[] :: [k2]) (ys :: k1) (ys :: k1) Source # 
Instance details

Defined in Data.HList.HList

(x' ~ x, HStripPrefix xs xsys ys) => HStripPrefix (x' ': xs :: [a]) (x ': xsys :: [a]) (ys :: k) Source # 
Instance details

Defined in Data.HList.HList

class HStripPrefix xs xsys ys => HAppendList1 (xs :: [k]) (ys :: [k]) (xsys :: [k]) | xs ys -> xsys, xs xsys -> ys Source #

HAppendList1 xs ys xsys is the type-level way of saying xs ++ ys == xsys

used by HSplitAt

Instances

Instances details
HAppendList1 ('[] :: [k]) (ys :: [k]) (ys :: [k]) Source # 
Instance details

Defined in Data.HList.HList

HAppendList1 xs ys zs => HAppendList1 (x ': xs :: [a]) (ys :: [a]) (x ': zs :: [a]) Source # 
Instance details

Defined in Data.HList.HList

class HLengthGe (xs :: [*]) (n :: HNat) Source #

HLengthGe xs n says that HLength xs >= n.

unlike the expression with a type family HLength, ghc assumes xs ~ (aFresh ': bFresh) when given a constraint HLengthGe xs (HSucc HZero)

Instances

Instances details
HLengthGe xxs 'HZero Source # 
Instance details

Defined in Data.HList.HList

(HLengthGe xs n, xxs ~ (x ': xs)) => HLengthGe xxs ('HSucc n) Source # 
Instance details

Defined in Data.HList.HList

class HLengthEq2 (xs :: [*]) n | xs -> n Source #

Instances

Instances details
zero ~ 'HZero => HLengthEq2 ('[] :: [Type]) (zero :: HNat) Source # 
Instance details

Defined in Data.HList.HList

(HLengthEq xs n, sn ~ 'HSucc n) => HLengthEq2 (x ': xs) (sn :: HNat) Source # 
Instance details

Defined in Data.HList.HList

class HLengthEq1 (xs :: [*]) n Source #

Instances

Instances details
xxs ~ ('[] :: [Type]) => HLengthEq1 xxs 'HZero Source # 
Instance details

Defined in Data.HList.HList

(HLengthEq xs n, xxs ~ (x ': xs)) => HLengthEq1 xxs ('HSucc n :: HNat) Source # 
Instance details

Defined in Data.HList.HList

class (SameLength' (HReplicateR n ()) xs, HLengthEq1 xs n, HLengthEq2 xs n) => HLengthEq (xs :: [*]) (n :: HNat) | xs -> n Source #

a better way to write HLength xs ~ n because:

  1. it works properly with ghc-7.10 (probably another example of ghc bug #10009)
  2. it works backwards a bit in that if n is known, then xs can be refined:
>>> undefined :: HLengthEq xs HZero => HList xs
H[]

Instances

Instances details
(SameLength' (HReplicateR n ()) xs, HLengthEq1 xs n, HLengthEq2 xs n) => HLengthEq xs n Source # 
Instance details

Defined in Data.HList.HList

class HSplitAt1 accum (n :: HNat) xsys xs ys | accum n xsys -> xs ys where Source #

helper for HSplitAt

Methods

hSplitAt1 :: HList accum -> Proxy n -> HList xsys -> (HList xs, HList ys) Source #

Instances

Instances details
HRevApp accum ('[] :: [Type]) xs => HSplitAt1 accum 'HZero ys xs ys Source # 
Instance details

Defined in Data.HList.HList

Methods

hSplitAt1 :: HList accum -> Proxy 'HZero -> HList ys -> (HList xs, HList ys) Source #

HSplitAt1 (b ': accum) n bs xs ys => HSplitAt1 accum ('HSucc n) (b ': bs) xs ys Source # 
Instance details

Defined in Data.HList.HList

Methods

hSplitAt1 :: HList accum -> Proxy ('HSucc n) -> HList (b ': bs) -> (HList xs, HList ys) Source #

class (HLengthEq xs n, HAppendList1 xs ys xsys) => HSplitAt (n :: HNat) xsys xs ys | n xsys -> xs ys, xs ys -> xsys, xs -> n where Source #

splitAt

setup

>>> let two = hSucc (hSucc hZero)
>>> let xsys = hEnd $ hBuild 1 2 3 4

If a length is explicitly provided, the resulting lists are inferred

>>> hSplitAt two xsys
(H[1,2],H[3,4])
>>> let sameLength_ :: SameLength a b => r a -> r b -> r a; sameLength_ = const
>>> let len2 x = x `sameLength_` HCons () (HCons () HNil)

If the first chunk of the list (a) has to be a certain length, the type of the Proxy argument can be inferred.

>>> case hSplitAt Proxy xsys of (a,b) -> (len2 a, b)
(H[1,2],H[3,4])

Methods

hSplitAt :: Proxy n -> HList xsys -> (HList xs, HList ys) Source #

Instances

Instances details
(HSplitAt1 ('[] :: [Type]) n xsys xs ys, HAppendList1 xs ys xsys, HLengthEq xs n) => HSplitAt n xsys xs ys Source # 
Instance details

Defined in Data.HList.HList

Methods

hSplitAt :: Proxy n -> HList xsys -> (HList xs, HList ys) Source #

class HSplit l where Source #

Analogus to Data.List.partition snd. See also HPartition

>>> let (.=.) :: p x -> y -> Tagged x y; _ .=. y = Tagged y
>>> hSplit $ hTrue .=. 2 .*. hTrue .=. 3 .*. hFalse .=. 1 .*. HNil
(H[2,3],H[1])

it might make more sense to instead have LVPair Bool e instead of (e, Proxy Bool) since the former has the same runtime representation as e

Associated Types

type HSplitT l :: [*] Source #

type HSplitF l :: [*] Source #

Methods

hSplit :: HList l -> (HList (HSplitT l), HList (HSplitF l)) Source #

Instances

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

Defined in Data.HList.HList

Associated Types

type HSplitT '[] :: [Type] Source #

type HSplitF '[] :: [Type] Source #

Methods

hSplit :: HList '[] -> (HList (HSplitT '[]), HList (HSplitF '[])) Source #

HSplit l => HSplit (Tagged 'False e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT (Tagged 'False e ': l) :: [Type] Source #

type HSplitF (Tagged 'False e ': l) :: [Type] Source #

Methods

hSplit :: HList (Tagged 'False e ': l) -> (HList (HSplitT (Tagged 'False e ': l)), HList (HSplitF (Tagged 'False e ': l))) Source #

HSplit l => HSplit (Tagged 'True e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT (Tagged 'True e ': l) :: [Type] Source #

type HSplitF (Tagged 'True e ': l) :: [Type] Source #

Methods

hSplit :: HList (Tagged 'True e ': l) -> (HList (HSplitT (Tagged 'True e ': l)), HList (HSplitF (Tagged 'True e ': l))) Source #

HSplit l => HSplit ((e, Proxy 'False) ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT ((e, Proxy 'False) ': l) :: [Type] Source #

type HSplitF ((e, Proxy 'False) ': l) :: [Type] Source #

Methods

hSplit :: HList ((e, Proxy 'False) ': l) -> (HList (HSplitT ((e, Proxy 'False) ': l)), HList (HSplitF ((e, Proxy 'False) ': l))) Source #

HSplit l => HSplit ((e, Proxy 'True) ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HSplitT ((e, Proxy 'True) ': l) :: [Type] Source #

type HSplitF ((e, Proxy 'True) ': l) :: [Type] Source #

Methods

hSplit :: HList ((e, Proxy 'True) ': l) -> (HList (HSplitT ((e, Proxy 'True) ': l)), HList (HSplitF ((e, Proxy 'True) ': l))) Source #

data HRmTag Source #

Constructors

HRmTag 

Instances

Instances details
e' ~ e => ApplyAB HRmTag (e, t) e' Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HRmTag -> (e, t) -> e' Source #

data HAddTag t Source #

Constructors

HAddTag t 

Instances

Instances details
et ~ (e, t) => ApplyAB (HAddTag t) e et Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HAddTag t -> e -> et Source #

data HFromJust Source #

Constructors

HFromJust 

Instances

Instances details
hJustA ~ HJust a => ApplyAB HFromJust hJustA a Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HFromJust -> hJustA -> a Source #

class FromHJustR (ToHJustR l) ~ l => FromHJust l where Source #

Associated Types

type FromHJustR l :: [*] Source #

Methods

fromHJust :: HList l -> HList (FromHJustR l) Source #

Instances

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

Defined in Data.HList.HList

Associated Types

type FromHJustR '[] :: [Type] Source #

Methods

fromHJust :: HList '[] -> HList (FromHJustR '[]) Source #

FromHJust l => FromHJust (HJust e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type FromHJustR (HJust e ': l) :: [Type] Source #

Methods

fromHJust :: HList (HJust e ': l) -> HList (FromHJustR (HJust e ': l)) Source #

FromHJust l => FromHJust (HNothing ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type FromHJustR (HNothing ': l) :: [Type] Source #

Methods

fromHJust :: HList (HNothing ': l) -> HList (FromHJustR (HNothing ': l)) Source #

class FromHJustR (ToHJustR l) ~ l => ToHJust l where Source #

the same as map Just

>>> toHJust (2 .*. 'a' .*. HNil)
H[HJust 2,HJust 'a']
>>> toHJust2 (2 .*. 'a' .*. HNil)
H[HJust 2,HJust 'a']

Associated Types

type ToHJustR l :: [*] Source #

Methods

toHJust :: HList l -> HList (ToHJustR l) Source #

Instances

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

Defined in Data.HList.HList

Associated Types

type ToHJustR '[] :: [Type] Source #

Methods

toHJust :: HList '[] -> HList (ToHJustR '[]) Source #

ToHJust l => ToHJust (e ': l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type ToHJustR (e ': l) :: [Type] Source #

Methods

toHJust :: HList (e ': l) -> HList (ToHJustR (e ': l)) Source #

class HList2List l e | l -> e where Source #

hMapOut id is similar, except this function is restricted to HLists that actually contain a value (so the list produced will be nonempty). This restriction allows adding a functional dependency, which means that less type annotations can be necessary.

Methods

hList2List :: HList l -> [e] Source #

list2HListSuffix :: [e] -> Maybe (HList l, [e]) Source #

Instances

Instances details
HList2List (e' ': l) e => HList2List (e ': (e' ': l)) e Source # 
Instance details

Defined in Data.HList.HList

Methods

hList2List :: HList (e ': (e' ': l)) -> [e] Source #

list2HListSuffix :: [e] -> Maybe (HList (e ': (e' ': l)), [e]) Source #

HList2List '[e] e Source # 
Instance details

Defined in Data.HList.HList

Methods

hList2List :: HList '[e] -> [e] Source #

list2HListSuffix :: [e] -> Maybe (HList '[e], [e]) Source #

class HTIntersectBool (b :: Bool) h t l1 l2 | b h t l1 -> l2 where Source #

Methods

hTIntersectBool :: Proxy b -> h -> HList t -> HList l1 -> HList l2 Source #

Instances

Instances details
HTIntersect t l1 l2 => HTIntersectBool 'False h t l1 l2 Source # 
Instance details

Defined in Data.HList.HList

Methods

hTIntersectBool :: Proxy 'False -> h -> HList t -> HList l1 -> HList l2 Source #

HTIntersect t l1 l2 => HTIntersectBool 'True h t l1 (h ': l2) Source # 
Instance details

Defined in Data.HList.HList

Methods

hTIntersectBool :: Proxy 'True -> h -> HList t -> HList l1 -> HList (h ': l2) Source #

class HTIntersect l1 l2 l3 | l1 l2 -> l3 where Source #

Methods

hTIntersect :: HList l1 -> HList l2 -> HList l3 Source #

Instances

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

Defined in Data.HList.HList

Methods

hTIntersect :: HList '[] -> HList l -> HList '[] Source #

(HTMember h l1 b, HTIntersectBool b h t l1 l2) => HTIntersect (h ': t) l1 l2 Source # 
Instance details

Defined in Data.HList.HList

Methods

hTIntersect :: HList (h ': t) -> HList l1 -> HList l2 Source #

class HTMember e (l :: [*]) (b :: Bool) | e l -> b Source #

could be an associated type if HEq had one

Instances

Instances details
HTMember (e :: k) ('[] :: [Type]) 'False Source # 
Instance details

Defined in Data.HList.HList

(HEq e e' b, HTMember e l b', HOr b b' ~ b'') => HTMember (e :: Type) (e' ': l) b'' Source # 
Instance details

Defined in Data.HList.HList

class HFind2 (b :: Bool) (e :: k) (l :: [k]) (l0 :: [k]) (n :: HNat) | b e l -> n Source #

Instances

Instances details
HFind2 'True (e :: k) (l :: [k]) (l0 :: [k]) 'HZero Source # 
Instance details

Defined in Data.HList.HList

HFind1 e l l0 n => HFind2 'False (e :: k) (l :: [k]) (l0 :: [k]) ('HSucc n) Source # 
Instance details

Defined in Data.HList.HList

class HFind1 (e :: k) (l :: [k]) (l0 :: [k]) (n :: HNat) | e l -> n Source #

Instances

Instances details
Fail (FieldNotFound e1 l0) => HFind1 (e1 :: k) ('[] :: [k]) (l0 :: [k]) 'HZero Source # 
Instance details

Defined in Data.HList.HList

(HEq e1 e2 b, HFind2 b e1 l l0 n) => HFind1 (e1 :: a) (e2 ': l :: [a]) (l0 :: [a]) n Source # 
Instance details

Defined in Data.HList.HList

class HFind1 e l l n => HFind (e :: k) (l :: [k]) (n :: HNat) | e l -> n Source #

It is a pure type-level operation

Instances

Instances details
HFind1 e l l n => HFind (e :: k) (l :: [k]) n Source # 
Instance details

Defined in Data.HList.HList

class HMemberM2 (b :: Maybe [k]) (e1 :: k) (l :: [k]) (r :: Maybe [k]) | b e1 l -> r Source #

Instances

Instances details
HMemberM2 ('Nothing :: Maybe [k]) (e1 :: k) (l :: [k]) ('Nothing :: Maybe [k]) Source # 
Instance details

Defined in Data.HList.HList

HMemberM2 ('Just l1 :: Maybe [a]) (e1 :: a) (e ': l :: [a]) ('Just (e ': l1) :: Maybe [a]) Source # 
Instance details

Defined in Data.HList.HList

class HMemberM1 (b :: Bool) (e1 :: k) (l :: [k]) (r :: Maybe [k]) | b e1 l -> r Source #

Instances

Instances details
(HMemberM e1 l r, HMemberM2 r e1 (e ': l) res) => HMemberM1 'False (e1 :: a) (e ': l :: [a]) (res :: Maybe [a]) Source # 
Instance details

Defined in Data.HList.HList

HMemberM1 'True (e1 :: k) (e ': l :: [k]) ('Just l :: Maybe [k]) Source # 
Instance details

Defined in Data.HList.HList

class HMemberM (e1 :: k) (l :: [k]) (r :: Maybe [k]) | e1 l -> r Source #

Check to see if an element e occurs in a list l If not, return 'Nothing If the element does occur, return 'Just l1 where l1 is a type-level list without e

Instances

Instances details
HMemberM (e1 :: k) ('[] :: [k]) ('Nothing :: Maybe [k]) Source # 
Instance details

Defined in Data.HList.HList

(HEq e1 e b, HMemberM1 b e1 (e ': l) res) => HMemberM (e1 :: a) (e ': l :: [a]) (res :: Maybe [a]) Source # 
Instance details

Defined in Data.HList.HList

type family HMemberP' pred e1 (l :: [*]) pb :: Bool Source #

Instances

Instances details
type HMemberP' pred e1 l (Proxy 'False) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP' pred e1 l (Proxy 'False) = HMemberP pred e1 l
type HMemberP' pred e1 l (Proxy 'True) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP' pred e1 l (Proxy 'True) = 'True

type family HMemberP pred e1 (l :: [*]) :: Bool Source #

The following is a similar type-only membership test It uses the user-supplied curried type equality predicate pred

Instances

Instances details
type HMemberP pred e1 ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP pred e1 ('[] :: [Type]) = 'False
type HMemberP pred e1 (e ': l) Source # 
Instance details

Defined in Data.HList.HList

type HMemberP pred e1 (e ': l) = HMemberP' pred e1 l (ApplyR pred (e1, e))

class HMember' (b0 :: Bool) (e1 :: k) (l :: [k]) (b :: Bool) | b0 e1 l -> b Source #

Instances

Instances details
HMember e1 l br => HMember' 'False (e1 :: k) (l :: [k]) br Source # 
Instance details

Defined in Data.HList.HList

HMember' 'True (e1 :: k) (l :: [k]) 'True Source # 
Instance details

Defined in Data.HList.HList

class HMember (e1 :: k) (l :: [k]) (b :: Bool) | e1 l -> b Source #

Check to see if an HList contains an element with a given type This is a type-level only test

Instances

Instances details
HMember (e1 :: k) ('[] :: [k]) 'False Source # 
Instance details

Defined in Data.HList.HList

(HEq e1 e b, HMember' b e1 l br) => HMember (e1 :: a) (e ': l :: [a]) br Source # 
Instance details

Defined in Data.HList.HList

type family HNats (l :: [*]) :: [HNat] Source #

We do so constructively, converting the HList whose elements are Proxy HNat to [HNat]. The latter kind is unpopulated and is present only at the type level.

Instances

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

Defined in Data.HList.HList

type HNats ('[] :: [Type]) = '[] :: [HNat]
type HNats (Proxy n ': l) Source # 
Instance details

Defined in Data.HList.HList

type HNats (Proxy n ': l) = n ': HNats l

type HMapOut f l e = HFoldr (Mapcar f) [e] l [e] Source #

newtype Mapcar f Source #

Constructors

Mapcar f 

Instances

Instances details
(l ~ [e'], ApplyAB f e e', el ~ (e, l)) => ApplyAB (Mapcar f) el l Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: Mapcar f -> el -> l Source #

class (Applicative m, SameLength a b) => HSequence m a b | a -> b, m b -> a where Source #

A heterogeneous version of

sequenceA :: (Applicative m) => [m a] -> m [a]

Only now we operate on heterogeneous lists, where different elements may have different types a. In the argument list of monadic values (m a_i), although a_i may differ, the monad m must be the same for all elements. That's why we needed Data.HList.TypeCastGeneric2 (currently (~)). The typechecker will complain if we attempt to use hSequence on a HList of monadic values with different monads.

The hSequence problem was posed by Matthias Fischmann in his message on the Haskell-Cafe list on Oct 8, 2006

http://www.haskell.org/pipermail/haskell-cafe/2006-October/018708.html

http://www.haskell.org/pipermail/haskell-cafe/2006-October/018784.html

Maybe
>>> hSequence $ Just (1 :: Integer) `HCons` (Just 'c') `HCons` HNil
Just H[1,'c']
>>> hSequence $  return 1 `HCons` Just  'c' `HCons` HNil
Just H[1,'c']
List
>>> hSequence $ [1] `HCons` ['c'] `HCons` HNil
[H[1,'c']]

Methods

hSequence :: HList a -> m (HList b) Source #

Instances

Instances details
Applicative m => HSequence m ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hSequence :: HList '[] -> m (HList '[]) Source #

(m1 ~ m, Applicative m, HSequence m as bs) => HSequence m (m1 a ': as) (a ': bs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hSequence :: HList (m1 a ': as) -> m (HList (a ': bs)) Source #

class HMapAux (r :: [*] -> *) f (x :: [*]) (y :: [*]) Source #

Minimal complete definition

hMapAux

Instances

Instances details
HMapAux HList (HFmap f) x y => HMapAux Record f x y Source # 
Instance details

Defined in Data.HList.Record

Methods

hMapAux :: f -> Record x -> Record y Source #

(ApplyAB f (GetElemTy x) (GetElemTy y), IArray UArray (GetElemTy y), IArray UArray (GetElemTy x)) => HMapAux RecordU f x y Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hMapAux :: f -> RecordU x -> RecordU y Source #

HMapAux Variant f xs ys => HMapAux TIC f xs ys Source # 
Instance details

Defined in Data.HList.TIC

Methods

hMapAux :: f -> TIC xs -> TIC ys Source #

HMapAux HList f ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hMapAux :: f -> HList '[] -> HList '[] Source #

(ApplyAB f e e', HMapAux HList f l l', SameLength l l') => HMapAux HList f (e ': l) (e' ': l') Source # 
Instance details

Defined in Data.HList.HList

Methods

hMapAux :: f -> HList (e ': l) -> HList (e' ': l') Source #

(ApplyAB f te te', HMapCxt Variant f (l ': ls) (l' ': ls')) => HMapAux Variant f (te ': (l ': ls)) (te' ': (l' ': ls')) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hMapAux :: f -> Variant (te ': (l ': ls)) -> Variant (te' ': (l' ': ls')) Source #

ApplyAB f te te' => HMapAux Variant f '[te] '[te'] Source # 
Instance details

Defined in Data.HList.Variant

Methods

hMapAux :: f -> Variant '[te] -> Variant '[te'] Source #

class (SameLength a b, HMapAux r f a b) => HMapCxt r f a b Source #

Instances

Instances details
(SameLength a b, HMapAux r f a b) => HMapCxt r f a b Source # 
Instance details

Defined in Data.HList.HList

newtype HMapL f Source #

Constructors

HMapL f 

Instances

Instances details
(HMapCxt HList f a b, as ~ HList a, bs ~ HList b) => ApplyAB (HMapL f) as bs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HMapL f -> as -> bs Source #

newtype HMap f Source #

hMap is written such that the length of the result list can be determined from the length of the argument list (and the other way around). Similarly, the type of the elements of the list is propagated in both directions too.

>>> :set -XNoMonomorphismRestriction
>>> let xs = 1 .*. 'c' .*. HNil
>>> :t hMap (HJust ()) xs
hMap (HJust ()) xs :: Num y => HList '[HJust y, HJust Char]

These 4 examples show that the constraint on the length (2 in this case) can be applied before or after the hMap. That inference is independent of the direction that type information is propagated for the individual elements.

>>> let asLen2 xs = xs `asTypeOf` (undefined :: HList '[a,b])
>>> let lr xs = asLen2 (applyAB (HMap HRead) xs)
>>> let ls xs = asLen2 (applyAB (HMap HShow) xs)
>>> let rl xs = applyAB (HMap HRead) (asLen2 xs)
>>> let sl xs = applyAB (HMap HShow) (asLen2 xs)
>>> :t lr
lr
  :: (Read ..., Read ...) => HList '[String, String] -> HList '[..., ...]
>>> :t rl
rl
  :: (Read ..., Read ...) => HList '[String, String] -> HList '[..., ...]
>>> :t ls
ls
  :: (Show ..., Show ...) => HList '[..., ...] -> HList '[String, String]
>>> :t sl
sl
  :: (Show ..., Show ...) => HList '[..., ...] -> HList '[String, String]

Constructors

HMap f 

Instances

Instances details
(HMapCxt r f a b, as ~ r a, bs ~ r b) => ApplyAB (HMap f) as bs Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: HMap f -> as -> bs Source #

class HAppendFD a b ab | a b -> ab where Source #

Methods

hAppendFD :: HList a -> HList b -> HList ab Source #

Instances

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

Defined in Data.HList.HList

Methods

hAppendFD :: HList '[] -> HList b -> HList b Source #

HAppendFD as bs cs => HAppendFD (a ': as) bs (a ': cs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hAppendFD :: HList (a ': as) -> HList bs -> HList (a ': cs) Source #

class HConcatFD xxs xs | xxs -> xs where Source #

Methods

hConcatFD :: HList xxs -> HList xs Source #

Instances

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

Defined in Data.HList.HList

Methods

hConcatFD :: HList '[] -> HList '[] Source #

(HConcatFD as bs, HAppendFD a bs cs) => HConcatFD (HList a ': as) cs Source # 
Instance details

Defined in Data.HList.HList

Methods

hConcatFD :: HList (HList a ': as) -> HList cs Source #

type family UnHList a :: [*] Source #

Instances

Instances details
type UnHList (HList a) Source # 
Instance details

Defined in Data.HList.HList

type UnHList (HList a) = a

type family HConcatR (a :: [*]) :: [*] Source #

Instances

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

Defined in Data.HList.HList

type HConcatR ('[] :: [Type]) = '[] :: [Type]
type HConcatR (x ': xs) Source # 
Instance details

Defined in Data.HList.HList

type HConcatR (x ': xs) = HAppendListR (UnHList x) (HConcatR xs)

type HConcat xs = HConcatFD xs (HConcatR xs) Source #

Like concat but for HLists of HLists.

Works in ghci... puzzling as what is different in doctest (it isn't -XExtendedDefaultRules)

>>> let a = hEnd $ hBuild 1 2 3
>>> let b = hEnd $ hBuild 'a' "abc"
>>> hConcat $ hBuild a b
H[1,2,3,'a',"abc"]

class HLengthEq r n => HIterate n f z r where Source #

This function behaves like iterate, with an extra argument to help figure out the result length

>>> let three = hSucc (hSucc (hSucc hZero))
>>> let f = Fun Just :: Fun '() Maybe
>>> :t applyAB f
applyAB f :: a -> Maybe a

f is applied to different types:

>>> hIterate three f ()
H[(),Just (),Just (Just ())]

It is also possible to specify the length later on, as done with Prelude.iterate

>>> let take3 x | _ <- hLength x `asTypeOf` three = x
>>> take3 $ hIterate Proxy f ()
H[(),Just (),Just (Just ())]

Methods

hIterate :: HLengthEq r n => Proxy n -> f -> z -> HList r Source #

Instances

Instances details
HIterate 'HZero f z ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hIterate :: Proxy 'HZero -> f -> z -> HList '[] Source #

(ApplyAB f z z', HIterate n f z' r', z ~ z_) => HIterate ('HSucc n) f z (z_ ': r') Source # 
Instance details

Defined in Data.HList.HList

Methods

hIterate :: Proxy ('HSucc n) -> f -> z -> HList (z_ ': r') Source #

class HLengthEq r n => HReplicateF (n :: HNat) f z r | r -> n where Source #

HReplicate produces lists that can be converted to ordinary lists

>>> let two = hSucc (hSucc hZero)
>>> let f = Fun' fromInteger :: Fun' Num Integer
>>> :t applyAB f
applyAB f :: Num b => Integer -> b
>>> hReplicateF two f 3
H[3,3]
>>> hReplicateF Proxy f 3 :: HList [Int, Double, Integer]
H[3,3.0,3]

Methods

hReplicateF :: HLengthEq r n => Proxy n -> f -> z -> HList r Source #

Instances

Instances details
HReplicateF 'HZero f z ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hReplicateF :: Proxy 'HZero -> f -> z -> HList '[] Source #

(ApplyAB f z fz, HReplicateF n f z r') => HReplicateF ('HSucc n) f z (fz ': r') Source # 
Instance details

Defined in Data.HList.HList

Methods

hReplicateF :: Proxy ('HSucc n) -> f -> z -> HList (fz ': r') Source #

type family HReplicateR (n :: HNat) (e :: k) :: [k] Source #

would be associated with HReplicate except we want it to work with e of any kind, not just * that you can put into a HList. An "inverse" of HLength

Instances

Instances details
type HReplicateR 'HZero (e :: k) Source # 
Instance details

Defined in Data.HList.HList

type HReplicateR 'HZero (e :: k) = '[] :: [k]
type HReplicateR ('HSucc n) (e :: k) Source # 
Instance details

Defined in Data.HList.HList

type HReplicateR ('HSucc n) (e :: k) = e ': HReplicateR n e

class HLengthEq es n => HReplicateFD (n :: HNat) e es | n e -> es, es -> n where Source #

Sometimes the result type can fix the type of the first argument:

>>> hReplicate Proxy () :: HList '[ (), (), () ]
H[(),(),()]

However, with HReplicate all elements must have the same type, so it may be easier to use HList2List:

>>> list2HList (repeat 3) :: Maybe (HList [Int, Int, Int])
Just H[3,3,3]

Methods

hReplicate :: Proxy n -> e -> HList es Source #

Instances

Instances details
HReplicateFD 'HZero e ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hReplicate :: Proxy 'HZero -> e -> HList '[] Source #

(HReplicateFD n e es, e ~ e') => HReplicateFD ('HSucc n) e (e' ': es) Source # 
Instance details

Defined in Data.HList.HList

Methods

hReplicate :: Proxy ('HSucc n) -> e -> HList (e' ': es) Source #

class HUnfoldFD p res z | p res -> z where Source #

Methods

hUnfold' :: p -> res -> HList z Source #

Instances

Instances details
HUnfoldFD p HNothing ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnfold' :: p -> HNothing -> HList '[] Source #

(Apply p s, HUnfoldFD p (ApplyR p s) z) => HUnfoldFD p (HJust (e, s)) (e ': z) Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnfold' :: p -> HJust (e, s) -> HList (e ': z) Source #

type HUnfold' p res = HUnfoldFD p (ApplyR p res) (HUnfold p res) Source #

type family HUnfoldR p res :: [*] Source #

Instances

Instances details
type HUnfoldR p HNothing Source # 
Instance details

Defined in Data.HList.HList

type HUnfoldR p HNothing = '[] :: [Type]
type HUnfoldR p (HJust (e, s)) Source # 
Instance details

Defined in Data.HList.HList

type HUnfoldR p (HJust (e, s)) = e ': HUnfoldR p (ApplyR p s)

type HUnfold p s = HUnfoldR p (ApplyR p s) Source #

class HFoldl f (z :: *) xs (r :: *) where Source #

like foldl

>>> hFoldl (uncurry $ flip (:)) [] (1 `HCons` 2 `HCons` HNil)
[2,1]

Methods

hFoldl :: f -> z -> HList xs -> r Source #

Instances

Instances details
z ~ z' => HFoldl f z ('[] :: [Type]) z' Source # 
Instance details

Defined in Data.HList.HList

Methods

hFoldl :: f -> z -> HList '[] -> z' Source #

(zx ~ (z, x), ApplyAB f zx z', HFoldl f z' xs r) => HFoldl f z (x ': xs) r Source # 
Instance details

Defined in Data.HList.HList

Methods

hFoldl :: f -> z -> HList (x ': xs) -> r Source #

class HFoldr1 f (l :: [*]) r where Source #

Methods

hFoldr1 :: f -> HList l -> r Source #

Instances

Instances details
(ApplyAB f (e, r) r', HFoldr1 f (e' ': l) r) => HFoldr1 f (e ': (e' ': l)) r' Source #

uses ApplyAB not Apply

Instance details

Defined in Data.HList.HList

Methods

hFoldr1 :: f -> HList (e ': (e' ': l)) -> r' Source #

v ~ v' => HFoldr1 f '[v] v' Source # 
Instance details

Defined in Data.HList.HList

Methods

hFoldr1 :: f -> HList '[v] -> v' Source #

class HScanr f z ls rs where Source #

Methods

hScanr :: f -> z -> HList ls -> HList rs Source #

Instances

Instances details
lz ~ '[z] => HScanr f z ('[] :: [Type]) lz Source # 
Instance details

Defined in Data.HList.HList

Methods

hScanr :: f -> z -> HList '[] -> HList lz Source #

(ApplyAB f (x, r) s, HScanr f z xs (r ': rs), srrs ~ (s ': (r ': rs))) => HScanr f z (x ': xs) srrs Source # 
Instance details

Defined in Data.HList.HList

Methods

hScanr :: f -> z -> HList (x ': xs) -> HList srrs Source #

class HFoldr f v (l :: [*]) r where Source #

Methods

hFoldr :: f -> v -> HList l -> r Source #

Instances

Instances details
v ~ v' => HFoldr f v ('[] :: [Type]) v' Source # 
Instance details

Defined in Data.HList.HList

Methods

hFoldr :: f -> v -> HList '[] -> v' Source #

(ApplyAB f (e, r) r', HFoldr f v l r) => HFoldr f v (e ': l) r' Source #

uses ApplyAB not Apply

Instance details

Defined in Data.HList.HList

Methods

hFoldr :: f -> v -> HList (e ': l) -> r' Source #

class HBuild' l r where Source #

Methods

hBuild' :: HList l -> r Source #

Instances

Instances details
HReverse l l' => HBuild' l (HList l') Source # 
Instance details

Defined in Data.HList.HList

Methods

hBuild' :: HList l -> HList l' Source #

(HReverse l lRev, HMapTaggedFn lRev l') => HBuild' l (Record l') Source #

This instance allows creating a Record with

hBuild 3 a :: Record '[Tagged "x" Int, Tagged "y" Char]
Instance details

Defined in Data.HList.Record

Methods

hBuild' :: HList l -> Record l' Source #

(HRevAppR l ('[] :: [Type]) ~ lRev, HExtendRs lRev (Proxy ('[] :: [Type])) ~ Proxy l1, l' ~ l1) => HBuild' l (Proxy l') Source #

see hEndP

Instance details

Defined in Data.HList.Record

Methods

hBuild' :: HList l -> Proxy l' Source #

HBuild' (a ': l) r => HBuild' l (a -> r) Source # 
Instance details

Defined in Data.HList.HList

Methods

hBuild' :: HList l -> a -> r Source #

class HReverse xs sx | xs -> sx, sx -> xs where Source #

Methods

hReverse :: HList xs -> HList sx Source #

Instances

Instances details
(HRevApp xs ('[] :: [Type]) sx, HRevApp sx ('[] :: [Type]) xs) => HReverse xs sx Source # 
Instance details

Defined in Data.HList.HList

Methods

hReverse :: HList xs -> HList sx Source #

class HRevApp l1 l2 l3 | l1 l2 -> l3 where Source #

Methods

hRevApp :: HList l1 -> HList l2 -> HList l3 Source #

Instances

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

Defined in Data.HList.HList

Methods

hRevApp :: HList '[] -> HList l2 -> HList l2 Source #

HRevApp l (x ': l') z => HRevApp (x ': l) l' z Source # 
Instance details

Defined in Data.HList.HList

Methods

hRevApp :: HList (x ': l) -> HList l' -> HList z Source #

type family HRevAppR (l1 :: [k]) (l2 :: [k]) :: [k] Source #

Instances

Instances details
type HRevAppR ('[] :: [k]) (l :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type HRevAppR ('[] :: [k]) (l :: [k]) = l
type HRevAppR (e ': l :: [a]) (l' :: [a]) Source # 
Instance details

Defined in Data.HList.HList

type HRevAppR (e ': l :: [a]) (l' :: [a]) = HRevAppR l (e ': l')

class HAppendList l1 l2 where Source #

Methods

hAppendList :: HList l1 -> HList l2 -> HList (HAppendListR l1 l2) Source #

the same as hAppend

Instances

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

Defined in Data.HList.HList

Methods

hAppendList :: HList '[] -> HList l2 -> HList (HAppendListR '[] l2) Source #

HAppendList l l' => HAppendList (x ': l) l' Source # 
Instance details

Defined in Data.HList.HList

Methods

hAppendList :: HList (x ': l) -> HList l' -> HList (HAppendListR (x ': l) l') Source #

type family HAppendListR (l1 :: [k]) (l2 :: [k]) :: [k] Source #

Instances

Instances details
type HAppendListR ('[] :: [k]) (l :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type HAppendListR ('[] :: [k]) (l :: [k]) = l
type HAppendListR (e ': l :: [k]) (l' :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type HAppendListR (e ': l :: [k]) (l' :: [k]) = e ': HAppendListR l l'

type family HLength (x :: [k]) :: HNat Source #

Length, but see HLengthEq instead

Instances

Instances details
type HLength ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type HLength ('[] :: [k]) = 'HZero
type HLength (x ': xs :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type HLength (x ': xs :: [k]) = 'HSucc (HLength xs)

class HInit xs where Source #

Associated Types

type HInitR xs :: [*] Source #

Methods

hInit :: HList xs -> HList (HInitR xs) Source #

Instances

Instances details
HInit (b ': c) => HInit (a ': (b ': c)) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HInitR (a ': (b ': c)) :: [Type] Source #

Methods

hInit :: HList (a ': (b ': c)) -> HList (HInitR (a ': (b ': c))) Source #

HInit '[x] Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HInitR '[x] :: [Type] Source #

Methods

hInit :: HList '[x] -> HList (HInitR '[x]) Source #

data ReadElement Source #

Constructors

ReadElement 

Instances

Instances details
(y ~ ReadP x, Read x) => ApplyAB ReadElement (Proxy x) y Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: ReadElement -> Proxy x -> y Source #

type family DropProxy (xs :: k) :: k Source #

inverse of AddProxy

Instances

Instances details
type DropProxy (Proxy x :: Type) Source # 
Instance details

Defined in Data.HList.HList

type DropProxy (Proxy x :: Type) = x
type DropProxy ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type DropProxy ('[] :: [k]) = '[] :: [k]
type DropProxy (x ': xs :: [a]) Source # 
Instance details

Defined in Data.HList.HList

type DropProxy (x ': xs :: [a]) = DropProxy x ': DropProxy xs

type family AddProxy (xs :: k) :: k Source #

Add Proxy to a type

>>> let x = undefined :: HList (AddProxy [Char,Int])
>>> :t x
x :: HList '[Proxy Char, Proxy Int]

Instances

Instances details
type AddProxy (x :: Type) Source # 
Instance details

Defined in Data.HList.HList

type AddProxy (x :: Type) = Proxy x
type AddProxy ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.HList

type AddProxy ('[] :: [k]) = '[] :: [k]
type AddProxy (x ': xs :: [a]) Source # 
Instance details

Defined in Data.HList.HList

type AddProxy (x ': xs :: [a]) = AddProxy x ': AddProxy xs

type HProxies xs = HProxiesFD xs (AddProxy xs) Source #

class HProxiesFD (xs :: [*]) pxs | pxs -> xs, xs -> pxs where Source #

creates a HList of Proxies

Methods

hProxies :: HList pxs Source #

Instances

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

Defined in Data.HList.HList

Methods

hProxies :: HList '[] Source #

HProxiesFD xs pxs => HProxiesFD (x ': xs) (Proxy x ': pxs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hProxies :: HList (Proxy x ': pxs) Source #

data family HList (l :: [*]) infixr 2 Source #

Instances

Instances details
(SameLengths '[x, y, xy], HZipList x y xy) => HUnzip HList x y xy Source # 
Instance details

Defined in Data.HList.HList

Methods

hUnzip :: HList xy -> (HList x, HList y) Source #

(SameLengths '[x, y, xy], HZipList x y xy) => HZip HList x y xy Source # 
Instance details

Defined in Data.HList.HList

Methods

hZip :: HList x -> HList y -> HList xy Source #

(HDeleteAtHNat n l, HType2HNat e l n, l' ~ HDeleteAtHNatR n l) => HDeleteAtLabel HList (e :: Type) l l' Source #

should this instead delete the first element of that type?

Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteAtLabel :: Label e -> HList l -> HList l' Source #

HMapAux HList f ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

Methods

hMapAux :: f -> HList '[] -> HList '[] Source #

(HEq e1 e b, HDeleteManyCase b e1 e l l1) => HDeleteMany (e1 :: Type) (HList (e ': l)) (HList l1) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteMany :: Proxy e1 -> HList (e ': l) -> HList l1 Source #

HDeleteMany (e :: k) (HList ('[] :: [Type])) (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteMany :: Proxy e -> HList '[] -> HList '[] Source #

(HSpanEqBy f a as fst snd, HGroupBy f snd gs) => HGroupBy (f :: t) (a ': as) (HList (a ': fst) ': gs) Source # 
Instance details

Defined in Data.HList.HList

Methods

hGroupBy :: Proxy f -> HList (a ': as) -> HList (HList (a ': fst) ': gs) Source #

(ApplyAB f e e', HMapAux HList f l l', SameLength l l') => HMapAux HList f (e ': l) (e' ': l') Source # 
Instance details

Defined in Data.HList.HList

Methods

hMapAux :: f -> HList (e ': l) -> HList (e' ': l') Source #

HReverse l l' => HBuild' l (HList l') Source # 
Instance details

Defined in Data.HList.HList

Methods

hBuild' :: HList l -> HList l' Source #

HExtend e (HList l) Source # 
Instance details

Defined in Data.HList.HList

Associated Types

type HExtendR e (HList l) Source #

Methods

(.*.) :: e -> HList l -> HExtendR e (HList l) Source #

(HOccurrence e (x ': y) l', HOccurs' e l' (x ': y)) => HOccurs e (HList (x ': y)) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs :: HList (x ': y) -> e Source #

(HOccurs e l, HProject l (HList l')) => HProject l (HList (e ': l')) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hProject :: l -> HList (e ': l') Source #

HInits1 a b => HInits a (HList ('[] :: [Type]) ': b) Source # 
Instance details

Defined in Data.HList.HList

Methods

hInits :: HList a -> HList (HList '[] ': b) Source #

(TypeRepsList (HList xs), Typeable x) => TypeRepsList (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.Data

Methods

typeRepsList :: HList (x ': xs) -> [TypeRep] Source #

TypeRepsList (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.Data

Methods

typeRepsList :: HList '[] -> [TypeRep] Source #

(Data x, Data (HList xs), TypeablePolyK (x ': xs), Typeable (HList (x ': xs))) => Data (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HList (x ': xs) -> c (HList (x ': xs)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HList (x ': xs)) #

toConstr :: HList (x ': xs) -> Constr #

dataTypeOf :: HList (x ': xs) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HList (x ': xs))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HList (x ': xs))) #

gmapT :: (forall b. Data b => b -> b) -> HList (x ': xs) -> HList (x ': xs) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HList (x ': xs) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HList (x ': xs) -> r #

gmapQ :: (forall d. Data d => d -> u) -> HList (x ': xs) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HList (x ': xs) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HList (x ': xs) -> m (HList (x ': xs)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HList (x ': xs) -> m (HList (x ': xs)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HList (x ': xs) -> m (HList (x ': xs)) #

Typeable (HList ('[] :: [Type])) => Data (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HList '[] -> c (HList '[]) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HList '[]) #

toConstr :: HList '[] -> Constr #

dataTypeOf :: HList '[] -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HList '[])) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HList '[])) #

gmapT :: (forall b. Data b => b -> b) -> HList '[] -> HList '[] #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HList '[] -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HList '[] -> r #

gmapQ :: (forall d. Data d => d -> u) -> HList '[] -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HList '[] -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HList '[] -> m (HList '[]) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HList '[] -> m (HList '[]) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HList '[] -> m (HList '[]) #

(HProxies a, HMapCxt HList ConstMempty (AddProxy a) a, HZip HList a a aa, HMapCxt HList UncurryMappend aa a) => Monoid (HList a) Source #

Analogous to the Monoid instance for tuples

>>> import Data.Monoid
>>> mempty :: HList '[(), All, [Int]]
H[(),All {getAll = True},[]]
>>> mappend (hBuild "a") (hBuild "b") :: HList '[String]
H["ab"]
Instance details

Defined in Data.HList.HList

Methods

mempty :: HList a #

mappend :: HList a -> HList a -> HList a #

mconcat :: [HList a] -> HList a #

(HZip HList a a aa, HMapCxt HList UncurryMappend aa a) => Semigroup (HList a) Source # 
Instance details

Defined in Data.HList.HList

Methods

(<>) :: HList a -> HList a -> HList a #

sconcat :: NonEmpty (HList a) -> HList a #

stimes :: Integral b => b -> HList a -> HList a #

(Bounded x, Bounded (HList xs)) => Bounded (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.HList

Methods

minBound :: HList (x ': xs) #

maxBound :: HList (x ': xs) #

Bounded (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

Methods

minBound :: HList '[] #

maxBound :: HList '[] #

(Ix x, Ix (HList xs)) => Ix (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.HList

Methods

range :: (HList (x ': xs), HList (x ': xs)) -> [HList (x ': xs)] #

index :: (HList (x ': xs), HList (x ': xs)) -> HList (x ': xs) -> Int #

unsafeIndex :: (HList (x ': xs), HList (x ': xs)) -> HList (x ': xs) -> Int #

inRange :: (HList (x ': xs), HList (x ': xs)) -> HList (x ': xs) -> Bool #

rangeSize :: (HList (x ': xs), HList (x ': xs)) -> Int #

unsafeRangeSize :: (HList (x ': xs), HList (x ': xs)) -> Int #

Ix (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

Methods

range :: (HList '[], HList '[]) -> [HList '[]] #

index :: (HList '[], HList '[]) -> HList '[] -> Int #

unsafeIndex :: (HList '[], HList '[]) -> HList '[] -> Int #

inRange :: (HList '[], HList '[]) -> HList '[] -> Bool #

rangeSize :: (HList '[], HList '[]) -> Int #

unsafeRangeSize :: (HList '[], HList '[]) -> Int #

(HProxies l, Read e, HSequence ReadP (ReadP e ': readP_l) (e ': l), HMapCxt HList ReadElement (AddProxy l) readP_l) => Read (HList (e ': l)) Source # 
Instance details

Defined in Data.HList.HList

Methods

readsPrec :: Int -> ReadS (HList (e ': l)) #

readList :: ReadS [HList (e ': l)] #

readPrec :: ReadPrec (HList (e ': l)) #

readListPrec :: ReadPrec [HList (e ': l)] #

Read (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

(Show e, Show (HList l)) => Show (HList (e ': l)) Source # 
Instance details

Defined in Data.HList.HList

Methods

showsPrec :: Int -> HList (e ': l) -> ShowS #

show :: HList (e ': l) -> String #

showList :: [HList (e ': l)] -> ShowS #

Show (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

Methods

showsPrec :: Int -> HList '[] -> ShowS #

show :: HList '[] -> String #

showList :: [HList '[]] -> ShowS #

(Eq x, Eq (HList xs)) => Eq (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.HList

Methods

(==) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(/=) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

Eq (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

Methods

(==) :: HList '[] -> HList '[] -> Bool #

(/=) :: HList '[] -> HList '[] -> Bool #

(Ord x, Ord (HList xs)) => Ord (HList (x ': xs)) Source # 
Instance details

Defined in Data.HList.HList

Methods

compare :: HList (x ': xs) -> HList (x ': xs) -> Ordering #

(<) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(<=) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(>) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

(>=) :: HList (x ': xs) -> HList (x ': xs) -> Bool #

max :: HList (x ': xs) -> HList (x ': xs) -> HList (x ': xs) #

min :: HList (x ': xs) -> HList (x ': xs) -> HList (x ': xs) #

Ord (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HList

Methods

compare :: HList '[] -> HList '[] -> Ordering #

(<) :: HList '[] -> HList '[] -> Bool #

(<=) :: HList '[] -> HList '[] -> Bool #

(>) :: HList '[] -> HList '[] -> Bool #

(>=) :: HList '[] -> HList '[] -> Bool #

max :: HList '[] -> HList '[] -> HList '[] #

min :: HList '[] -> HList '[] -> HList '[] #

HAppendList l1 l2 => HAppend (HList l1) (HList l2) Source # 
Instance details

Defined in Data.HList.HList

Methods

hAppend :: HList l1 -> HList l2 -> HAppendR (HList l1) (HList l2) Source #

HProject (HList l) (HList ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hProject :: HList l -> HList '[] Source #

ApplyAB f e e' => ApplyAB (MapCar f) (e, HList l) (HList (e' ': l)) Source # 
Instance details

Defined in Data.HList.HList

Methods

applyAB :: MapCar f -> (e, HList l) -> HList (e' ': l) Source #

HInits1 ('[] :: [Type]) '[HList ('[] :: [Type])] Source # 
Instance details

Defined in Data.HList.HList

Methods

hInits1 :: HList '[] -> HList '[HList '[]] Source #

HTails ('[] :: [Type]) '[HList ('[] :: [Type])] Source # 
Instance details

Defined in Data.HList.HList

Methods

hTails :: HList '[] -> HList '[HList '[]] Source #

(ch ~ Proxy (HBoolEQ sel (KMember n ns)), Apply (ch, FHUProj sel ns) (HList (e ': l), Proxy n)) => Apply (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: FHUProj sel ns -> (HList (e ': l), Proxy n) -> ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (FHUProj sel ns) (HList ('[] :: [Type]), n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList '[], n) Source #

Methods

apply :: FHUProj sel ns -> (HList '[], n) -> ApplyR (FHUProj sel ns) (HList '[], n) Source #

Apply (FHUProj sel ns) (HList l, Proxy ('HSucc n)) => Apply (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'False, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'True, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

(HConcatFD as bs, HAppendFD a bs cs) => HConcatFD (HList a ': as) cs Source # 
Instance details

Defined in Data.HList.HList

Methods

hConcatFD :: HList (HList a ': as) -> HList cs Source #

(HInits1 xs ys, HMapCxt HList (FHCons2 x) ys ys', HMapCons x ys ~ ys', HMapTail ys' ~ ys) => HInits1 (x ': xs) (HList '[x] ': ys') Source # 
Instance details

Defined in Data.HList.HList

Methods

hInits1 :: HList (x ': xs) -> HList (HList '[x] ': ys') Source #

HTails xs ys => HTails (x ': xs) (HList (x ': xs) ': ys) Source # 
Instance details

Defined in Data.HList.HList

Methods

hTails :: HList (x ': xs) -> HList (HList (x ': xs) ': ys) Source #

HMapUnboxF xs us => HMapUnboxF (HList x ': xs) (RecordU x ': us) Source # 
Instance details

Defined in Data.HList.RecordU

(HList (x ': y) ~ z, HZip3 xs ys zs) => HZip3 (x ': xs) (HList y ': ys) (z ': zs) Source # 
Instance details

Defined in Data.HList.HZip

Methods

hZip3 :: HList (x ': xs) -> HList (HList y ': ys) -> HList (z ': zs) Source #

type HExtendR e (HList l) Source # 
Instance details

Defined in Data.HList.HList

type HExtendR e (HList l) = HList (e ': l)
type HAppendR (HList l1 :: Type) (HList l2 :: Type) Source # 
Instance details

Defined in Data.HList.HList

type HAppendR (HList l1 :: Type) (HList l2 :: Type) = HList (HAppendListR l1 l2)
type HMapCons x (HList a ': b) Source # 
Instance details

Defined in Data.HList.HList

type HMapCons x (HList a ': b) = HList (x ': a) ': HMapCons x b
data HList ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.HList

data HList ('[] :: [Type]) = HNil
type UnHList (HList a) Source # 
Instance details

Defined in Data.HList.HList

type UnHList (HList a) = a
type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (Proxy (HBoolEQ sel (KMember n ns)), FHUProj sel ns) (HList (e ': l), Proxy n)
type ApplyR (FHUProj sel ns) (HList ('[] :: [Type]), n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList ('[] :: [Type]), n) = HNothing
type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (FHUProj sel ns) (HList l, Proxy ('HSucc n))
type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) = HJust (e, (HList l, Proxy ('HSucc n)))
data HList (x ': xs) Source # 
Instance details

Defined in Data.HList.HList

data HList (x ': xs) = x `HCons` (HList xs)
type HMapTail (HList (a ': as) ': bs) Source # 
Instance details

Defined in Data.HList.HList

type HMapTail (HList (a ': as) ': bs) = HList as ': HMapTail bs

hHead :: HList (e ': l) -> e Source #

hTail :: HList (e ': l) -> HList l Source #

hLast :: forall {l1 :: [Type]} {e} {l :: [Type]}. HRevApp l1 ('[] :: [Type]) (e ': l) => HList l1 -> e Source #

hLength :: HLengthEq l n => HList l -> Proxy n Source #

hReverse_ :: forall {l1 :: [Type]} {l3 :: [Type]}. HRevApp l1 ('[] :: [Type]) l3 => HList l1 -> HList l3 Source #

a version of hReverse that does not allow the type information to flow backwards

hEnd :: HList l -> HList l Source #

Note:

x :: HList a
means: forall a. x :: HList a
hEnd x
means: exists a. x :: HList a

List termination

hBuild :: HBuild' '[] r => r Source #

Building lists

hUnfold :: forall {f} {a} {z :: [Type]}. (HUnfoldFD f (ApplyR f a) z, Apply f a) => f -> a -> HList z Source #

hConcat :: HConcat xs => HList xs -> HList (HConcatR xs) Source #

hMap :: forall {a :: [Type]} {b :: [Type]} {r} {f}. (SameLength' a b, SameLength' b a, HMapAux r f a b) => f -> r a -> r b Source #

hMapL :: forall {a :: [Type]} {b :: [Type]} {f}. (SameLength' a b, SameLength' b a, HMapAux HList f a b) => f -> HList a -> HList b Source #

hMap constrained to HList

hComposeList :: HFoldr Comp (a -> a) l (t -> a) => HList l -> t -> a Source #

>>> let xs = length .*. (+1) .*. (*2) .*. HNil
>>> hComposeList xs "abc"
8

hMapOut :: forall f e l. HMapOut f l e => f -> HList l -> [e] Source #

compare hMapOut f with hList2List . hMap f

hMapM :: (Monad m, HMapOut f l (m e)) => f -> HList l -> [m e] Source #

mapM :: forall b m a. (Monad m) => (a -> m b) -> [a] -> m [b]

Likewise for mapM_.

See hSequence if the result list should also be heterogenous.

hMapM_ :: (Monad m, HMapOut f l (m ())) => f -> HList l -> m () Source #

GHC doesn't like its own type.

hMapM_ :: forall m a f e. (Monad m, HMapOut f a (m e)) => f -> a -> m ()

Without explicit type signature, it's Ok. Sigh. Anyway, Hugs does insist on a better type. So we restrict as follows:

hMember :: HMember e l b => Proxy e -> Proxy l -> Proxy b Source #

hTMember :: HTMember e l b => e -> HList l -> Proxy b Source #

list2HList :: HList2List l e => [e] -> Maybe (HList l) Source #

listAsHList :: forall {p} {f} {l1 :: [Type]} {e1} {l2 :: [Type]} {e2}. (Choice p, Applicative f, HList2List l1 e1, HList2List l2 e2) => p (HList l2) (f (HList l1)) -> p [e2] (f [e1]) Source #

Prism [s] [t] (HList s) (HList t)

listAsHList' :: forall {p} {f} {l :: [Type]} {e}. (Choice p, Applicative f, HList2List l e) => p (HList l) (f (HList l)) -> p [e] (f [e]) Source #

Prism' [a] (HList s)

where s ~ HReplicateR n a

toHJust2 :: (HMapCxt r (HJust ()) a b, ToHJust a, b ~ ToHJustR a) => r a -> r b Source #

alternative implementation. The Apply instance is in Data.HList.FakePrelude. A longer type could be inferred.

fromHJust2 :: HMapCxt r HFromJust a b => r a -> r b Source #

This implementation is shorter.

hAddTag :: forall {a :: [Type]} {b :: [Type]} {r} {t}. (SameLength' a b, SameLength' b a, HMapAux r (HAddTag t) a b) => t -> r a -> r b Source #

hRmTag :: forall {a :: [Type]} {b :: [Type]} {r}. (SameLength' a b, SameLength' b a, HMapAux r HRmTag a b) => r a -> r b Source #

hFlag :: forall {a :: [Type]} {b :: [Type]} {r}. (SameLength' a b, SameLength' b a, HMapAux r (HAddTag (Proxy 'True)) a b) => r a -> r b Source #

Annotate list with a type-level Boolean

hFlag :: HMapCxt (HAddTag (Proxy True)) l r => HList l -> HList r

hTuple :: forall {p} {f} {v1 :: [Type]} {a} {v2 :: [Type]} {b}. (Profunctor p, Functor f, HTuple v1 a, HTuple v2 b) => p a (f b) -> p (HList v1) (f (HList v2)) Source #

Iso (HList v) (HList v') a b

hTuple' :: forall {p} {f} {v :: [Type]} {a}. (Profunctor p, Functor f, HTuple v a) => p a (f a) -> p (HList v) (f (HList v)) Source #

Iso' (HList v) a

class HZipRecord x y xy | x y -> xy, xy -> x y where Source #

Methods

hZipRecord :: Record x -> Record y -> Record xy Source #

hUnzipRecord :: Record xy -> (Record x, Record y) Source #

Instances

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

Defined in Data.HList.Record

Methods

hZipRecord :: Record '[] -> Record '[] -> Record '[] Source #

hUnzipRecord :: Record '[] -> (Record '[], Record '[]) Source #

HZipRecord as bs abss => HZipRecord (Tagged x a ': as) (Tagged x b ': bs) (Tagged x (a, b) ': abss) Source # 
Instance details

Defined in Data.HList.Record

Methods

hZipRecord :: Record (Tagged x a ': as) -> Record (Tagged x b ': bs) -> Record (Tagged x (a, b) ': abss) Source #

hUnzipRecord :: Record (Tagged x (a, b) ': abss) -> (Record (Tagged x a ': as), Record (Tagged x b ': bs)) Source #

newtype HMapR f Source #

Constructors

HMapR f 

Instances

Instances details
(HMapCxt Record f x y, rx ~ Record x, ry ~ Record y) => ApplyAB (HMapR f) rx ry Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: HMapR f -> rx -> ry Source #

class HLensCxt x r s t a b => HLens x r s t a b | x s b -> t, x t a -> s, x s -> a, x t -> b where Source #

Methods

hLens :: Label x -> forall f. Functor f => (a -> f b) -> r s -> f (r t) Source #

hLens :: Label x -> Lens (r s) (r t) a b

Instances

Instances details
HLensCxt r x s t a b => HLens (r :: k) x s t a b Source # 
Instance details

Defined in Data.HList.Record

Methods

hLens :: Label r -> forall (f :: Type -> Type). Functor f => (a -> f b) -> x s -> f (x t) Source #

type HLensCxt x r s t a b = (HasField x (r s) a, HUpdateAtLabel r x b s t, HasField x (r t) b, HUpdateAtLabel r x a t s, SameLength s t, SameLabels s t) Source #

constraints needed to implement HLens

class HRearrange4 (l :: *) (ls :: [*]) rin rout r' | l ls rin rout -> r' where Source #

Helper class 2 for hRearrange

Methods

hRearrange4 :: proxy l -> Proxy ls -> HList rin -> HList rout -> HList r' Source #

Instances

Instances details
Fail (FieldNotFound l ()) => HRearrange4 l ls ('[] :: [Type]) rout ('[] :: [Type]) Source #

For improved error messages. XXX FieldNotFound

Instance details

Defined in Data.HList.Record

Methods

hRearrange4 :: proxy l -> Proxy ls -> HList '[] -> HList rout -> HList '[] Source #

(HRearrange3 ls rout r', r'' ~ (Tagged l v ': r'), ll ~ Label l) => HRearrange4 ll ls '[Tagged l v] rout r'' Source # 
Instance details

Defined in Data.HList.Record

Methods

hRearrange4 :: proxy ll -> Proxy ls -> HList '[Tagged l v] -> HList rout -> HList r'' Source #

class HRearrange3 (ls :: [*]) r r' | ls r -> r' where Source #

same as HRearrange, except no backwards FD

Methods

hRearrange3 :: proxy ls -> HList r -> HList r' Source #

Instances

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

Defined in Data.HList.Record

Methods

hRearrange3 :: proxy '[] -> HList '[] -> HList '[] Source #

Fail (ExtraField l) => HRearrange3 ('[] :: [Type]) (Tagged l v ': a) ('[] :: [Type]) Source #

For improved error messages

Instance details

Defined in Data.HList.Record

Methods

hRearrange3 :: proxy '[] -> HList (Tagged l v ': a) -> HList '[] Source #

(H2ProjectByLabels '[l] r rin rout, HRearrange4 l ls rin rout r', l ~ Label ll) => HRearrange3 (l ': ls) r r' Source # 
Instance details

Defined in Data.HList.Record

Methods

hRearrange3 :: proxy (l ': ls) -> HList r -> HList r' Source #

class (HRearrange3 ls r r', LabelsOf r' ~ ls, SameLength ls r, SameLength r r') => HRearrange (ls :: [*]) r r' | ls r -> r', r' -> ls where Source #

Helper class for hRearrange

Methods

hRearrange2 :: proxy ls -> HList r -> HList r' Source #

Instances

Instances details
(HRearrange3 ls r r', LabelsOf r' ~ ls, SameLength ls r, SameLength r r') => HRearrange ls r r' Source # 
Instance details

Defined in Data.HList.Record

Methods

hRearrange2 :: proxy ls -> HList r -> HList r' Source #

class Rearranged r s t a b where Source #

Methods

rearranged :: (Profunctor p, Functor f) => (r a `p` f (r b)) -> r s `p` f (r t) Source #

Instances

Instances details
(la ~ LabelsOf a, lt ~ LabelsOf t, HRearrange la s a, HRearrange lt b t, HLabelSet la, HLabelSet lt) => Rearranged Record (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]) Source #
Iso (Record s) (Record t) (Record a) (Record b)

where s is a permutation of a, b is a permutation of t. In practice sameLabels and sameLength are likely needed on both sides of rearranged, to avoid ambiguous types.

An alternative implementation:

rearranged x = iso hRearrange' hRearrange' x
Instance details

Defined in Data.HList.Record

Methods

rearranged :: (Profunctor p, Functor f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

(SameLength s a, ExtendsVariant s a, SameLength b t, ExtendsVariant b t) => Rearranged Variant (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

rearranged :: (Profunctor p, Functor f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

class UnionSymRec' (b :: Bool) r1 f2 r2' ru | b r1 f2 r2' -> ru where Source #

Methods

unionSR' :: Proxy b -> Record r1 -> f2 -> Record r2' -> (Record ru, Record ru) Source #

Instances

Instances details
(UnionSymRec r1 r2' ru, HExtend f2 (Record ru), Record f2ru ~ HExtendR f2 (Record ru)) => UnionSymRec' 'False r1 f2 r2' f2ru Source # 
Instance details

Defined in Data.HList.Record

Methods

unionSR' :: Proxy 'False -> Record r1 -> f2 -> Record r2' -> (Record f2ru, Record f2ru) Source #

(UnionSymRec r1 r2' ru, HTPupdateAtLabel Record l2 v2 ru, f2 ~ Tagged l2 v2) => UnionSymRec' 'True r1 f2 r2' ru Source #

Field f2 is already in r1, so it will be in the union of r1 with the rest of r2.

To inject (HCons f2 r2) in that union, we should replace the field f2

Instance details

Defined in Data.HList.Record

Methods

unionSR' :: Proxy 'True -> Record r1 -> f2 -> Record r2' -> (Record ru, Record ru) Source #

class UnionSymRec r1 r2 ru | r1 r2 -> ru where Source #

Methods

unionSR :: Record r1 -> Record r2 -> (Record ru, Record ru) Source #

Instances

Instances details
r1 ~ r1' => UnionSymRec r1 ('[] :: [Type]) r1' Source # 
Instance details

Defined in Data.HList.Record

Methods

unionSR :: Record r1 -> Record '[] -> (Record r1', Record r1') Source #

(HMemberLabel l r1 b, UnionSymRec' b r1 (Tagged l v) r2' ru) => UnionSymRec r1 (Tagged l v ': r2') ru Source # 
Instance details

Defined in Data.HList.Record

Methods

unionSR :: Record r1 -> Record (Tagged l v ': r2') -> (Record ru, Record ru) Source #

class HLeftUnion r r' r'' | r r' -> r'' where Source #

Methods

hLeftUnion :: Record r -> Record r' -> Record r'' Source #

Instances

Instances details
(HDeleteLabels (LabelsOf l) r r', HAppend (Record l) (Record r'), HAppendR (Record l) (Record r') ~ Record lr) => HLeftUnion l r lr Source # 
Instance details

Defined in Data.HList.Record

Methods

hLeftUnion :: Record l -> Record r -> Record lr Source #

class HDeleteLabels ks r r' | ks r -> r' where Source #

Methods

hDeleteLabels Source #

Arguments

:: proxy (ks :: [*])

as provided by labelsOf

-> Record r 
-> Record r' 

Instances

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

Defined in Data.HList.Record

Methods

hDeleteLabels :: proxy ks -> Record '[] -> Record '[] Source #

(HMember (Label l) ks b, HCond b (Record r2) (Record (Tagged l v ': r2)) (Record r3), HDeleteLabels ks r1 r2) => HDeleteLabels ks (Tagged l v ': r1) r3 Source # 
Instance details

Defined in Data.HList.Record

Methods

hDeleteLabels :: proxy ks -> Record (Tagged l v ': r1) -> Record r3 Source #

type HMemberLabel l r b = HMember l (UnLabel l (LabelsOf r)) b Source #

type HTPupdateAtLabel record l v r = (HUpdateAtLabel record l v r r, SameLength' r r) Source #

class H2ProjectByLabels' (b :: Maybe [*]) (ls :: [*]) r rin rout | b ls r -> rin rout where Source #

Methods

h2projectByLabels' :: Proxy b -> proxy ls -> HList r -> (HList rin, HList rout) Source #

Instances

Instances details
H2ProjectByLabels ls r rin rout => H2ProjectByLabels' ('Nothing :: Maybe [Type]) ls (f ': r) rin (f ': rout) Source #

if ls above has labels not in the record, we get labels (rin isSubsetOf ls).

Instance details

Defined in Data.HList.Record

Methods

h2projectByLabels' :: Proxy 'Nothing -> proxy ls -> HList (f ': r) -> (HList rin, HList (f ': rout)) Source #

H2ProjectByLabels ls1 r rin rout => H2ProjectByLabels' ('Just ls1) ls (f ': r) (f ': rin) rout Source # 
Instance details

Defined in Data.HList.Record

Methods

h2projectByLabels' :: Proxy ('Just ls1) -> proxy ls -> HList (f ': r) -> (HList (f ': rin), HList rout) Source #

class H2ProjectByLabels (ls :: [*]) r rin rout | ls r -> rin rout where Source #

Invariant:

r === rin `disjoint-union` rout
labels rin === ls
    where (rin,rout) = hProjectByLabels ls r

Methods

h2projectByLabels :: proxy ls -> HList r -> (HList rin, HList rout) Source #

Instances

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

Defined in Data.HList.Record

Methods

h2projectByLabels :: proxy '[] -> HList r -> (HList '[], HList r) Source #

H2ProjectByLabels (l ': ls) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.Record

Methods

h2projectByLabels :: proxy (l ': ls) -> HList '[] -> (HList '[], HList '[]) Source #

(HMemberM (Label l1) (l ': ls) b, H2ProjectByLabels' b (l ': ls) (Tagged l1 v1 ': r1) rin rout) => H2ProjectByLabels (l ': ls) (Tagged l1 v1 ': r1) rin rout Source # 
Instance details

Defined in Data.HList.Record

Methods

h2projectByLabels :: proxy (l ': ls) -> HList (Tagged l1 v1 ': r1) -> (HList rin, HList rout) Source #

type family Labels (xs :: [k]) :: * Source #

A helper to make the Proxy needed by hProjectByLabels, and similar functions which accept a list of kind [*].

For example:

(rin,rout) = hProjectByLabels2 (Proxy :: Labels ["x","y"]) r

behaves like

rin = r .!. (Label :: Label "x") .*.
      r .!. (Label :: Label "y") .*.
      emptyRecord

rout = r .-. (Label :: Label "x") .-. (Label :: Label "y")

Instances

Instances details
type Labels (xs :: [k]) Source # 
Instance details

Defined in Data.HList.Record

type Labels (xs :: [k])

class HUpdateAtLabel record (l :: k) (v :: *) (r :: [*]) (r' :: [*]) | l v r -> r', l r' -> v where Source #

hUpdateAtLabel label value record

Methods

hUpdateAtLabel :: SameLength r r' => Label l -> v -> record r -> record r' Source #

Instances

Instances details
(HUpdateAtLabel Record e' e r r', HTypeIndexed r', e ~ e') => HUpdateAtLabel TIP (e' :: Type) e r r' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hUpdateAtLabel :: Label e' -> e -> TIP r -> TIP r' Source #

(HUpdateAtLabel2 l v r r', HasField l (Record r') v) => HUpdateAtLabel Record (l :: k) v r r' Source # 
Instance details

Defined in Data.HList.Record

Methods

hUpdateAtLabel :: Label l -> v -> Record r -> Record r' Source #

(r ~ r', v ~ GetElemTy r, HFindLabel l r n, HNat2Integral n, IArray UArray v, HasField l (Record r') v) => HUpdateAtLabel RecordU (l :: k) v r r' Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hUpdateAtLabel :: Label l -> v -> RecordU r -> RecordU r' Source #

HUpdateVariantAtLabelCxt l e v v' n _e => HUpdateAtLabel Variant (l :: k) e v v' Source #
hUpdateAtLabel x e' (mkVariant x e proxy) == mkVariant x e' proxy
hUpdateAtLabel y e' (mkVariant x e proxy) == mkVariant x e  proxy
Instance details

Defined in Data.HList.Variant

Methods

hUpdateAtLabel :: Label l -> e -> Variant v -> Variant v' Source #

class HasField' (b :: Bool) (l :: k) (r :: [*]) v | b l r -> v where Source #

Methods

hLookupByLabel' :: Proxy b -> Label l -> HList r -> v Source #

Instances

Instances details
HasField l (Record r) v => HasField' 'False (l :: k) (fld ': r) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel' :: Proxy 'False -> Label l -> HList (fld ': r) -> v Source #

HasField' 'True (l :: k) (Tagged l v ': r) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel' :: Proxy 'True -> Label l -> HList (Tagged l v ': r) -> v Source #

class HasFieldM1 (b :: Maybe [*]) (l :: k) r v | b l r -> v where Source #

Methods

hLookupByLabelM1 :: Proxy b -> Label l -> r -> t -> DemoteMaybe t v Source #

Instances

Instances details
HasFieldM1 ('Nothing :: Maybe [Type]) (l :: k) r ('Nothing :: Maybe Type) Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabelM1 :: Proxy 'Nothing -> Label l -> r -> t -> DemoteMaybe t 'Nothing Source #

HasField l r v => HasFieldM1 ('Just b) (l :: k) r ('Just v) Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabelM1 :: Proxy ('Just b) -> Label l -> r -> t -> DemoteMaybe t ('Just v) Source #

type family DemoteMaybe (d :: *) (v :: Maybe *) :: * Source #

Instances

Instances details
type DemoteMaybe d ('Nothing :: Maybe Type) Source # 
Instance details

Defined in Data.HList.Record

type DemoteMaybe d ('Nothing :: Maybe Type) = d
type DemoteMaybe d ('Just a) Source # 
Instance details

Defined in Data.HList.Record

type DemoteMaybe d ('Just a) = a

class HasFieldM (l :: k) r (v :: Maybe *) | l r -> v where Source #

a version of HasField hLookupByLabel .!. that returns a default value when the label is not in the record:

>>> let r = x .=. "the x value" .*. emptyRecord
>>> hLookupByLabelM y r ()
()
>>> hLookupByLabelM x r ()
"the x value"

Methods

hLookupByLabelM Source #

Arguments

:: Label l 
-> r

Record (or Variant,TIP,TIC)

-> t

default value

-> DemoteMaybe t v 

Instances

Instances details
(HMemberM (Label l) (LabelsOf xs) b, HasFieldM1 b l (r xs) v) => HasFieldM (l :: k) (r xs) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabelM :: Label l -> r xs -> t -> DemoteMaybe t v Source #

class HasField (l :: k) r v | l r -> v where Source #

This is a baseline implementation. We use a helper class, HasField, to abstract from the implementation.

Because hLookupByLabel is so frequent and important, we implement it separately, more efficiently. The algorithm is familiar assq, only the comparison operation is done at compile-time

Methods

hLookupByLabel :: Label l -> r -> v Source #

Instances

Instances details
(e ~ e', HasField e (Record l) e') => HasField (e :: Type) (TIP l) e' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hLookupByLabel :: Label e -> TIP l -> e' Source #

(t ~ (Any :: Type), Fail (FieldNotFound l ())) => HasField (l :: k) (Record ('[] :: [Type])) t Source #

XXX

Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel :: Label l -> Record '[] -> t Source #

(IArray UArray v, v ~ GetElemTy ls, HFindLabel l ls n, HNat2Integral n) => HasField (l :: k) (RecordU ls) v Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByLabel :: Label l -> RecordU ls -> v Source #

(HFindLabel l r n, HLookupByHNatUS n u (Tagged l v), HasField l (Record r) v, RecordUSCxt r u) => HasField (l :: k) (RecordUS r) v Source #

works expected. See examples attached to bad.

Instance details

Defined in Data.HList.RecordU

Methods

hLookupByLabel :: Label l -> RecordUS r -> v Source #

(HEqK l l1 b, HasField' b l (Tagged l1 v1 ': r) v) => HasField (l :: k1) (Record (Tagged l1 v1 ': r)) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel :: Label l -> Record (Tagged l1 v1 ': r) -> v Source #

HasField o (Variant l) (Maybe o) => HasField (o :: Type) (TIC l) (Maybe o) Source #

Public destructor (or, open union's projection function)

Instance details

Defined in Data.HList.TIC

Methods

hLookupByLabel :: Label o -> TIC l -> Maybe o Source #

(HasField x (Record vs) a, HFindLabel x vs n, HNat2Integral n) => HasField (x :: k) (Variant vs) (Maybe a) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hLookupByLabel :: Label x -> Variant vs -> Maybe a Source #

data ReadComponent Source #

Instances

Instances details
(Read v, ShowLabel l, x ~ Tagged l v, ReadP x ~ y) => ApplyAB ReadComponent (Proxy x) y Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: ReadComponent -> Proxy x -> y Source #

class ShowComponents l where Source #

Instances

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

Defined in Data.HList.Record

(ShowLabel l, Show v, ShowComponents r) => ShowComponents (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

Methods

showComponents :: String -> HList (Tagged l v ': r) -> String Source #

class SameLength r (RecordValuesR r) => RecordValues (r :: [*]) where Source #

Construct the HList of values of the record.

Associated Types

type RecordValuesR r :: [*] Source #

Instances

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

Defined in Data.HList.Record

Associated Types

type RecordValuesR '[] :: [Type] Source #

(SameLength' r (RecordValuesR r), SameLength' (RecordValuesR r) r, RecordValues r) => RecordValues (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

Associated Types

type RecordValuesR (Tagged l v ': r) :: [Type] Source #

Methods

recordValues' :: HList (Tagged l v ': r) -> HList (RecordValuesR (Tagged l v ': r)) Source #

type HFindLabel (l :: k) (ls :: [*]) (n :: HNat) = HFind l (UnLabel l (LabelsOf ls)) n Source #

A version of HFind where the ls type variable is a list of Tagged or Label. This is a bit indirect, and ideally LabelsOf could have kind [*] -> [k].

type family UnLabel (proxy :: k) (ls :: [*]) :: [k] Source #

remove the Label type constructor. The proxy argument is supplied to make it easier to fix the kind variable k.

Instances

Instances details
type UnLabel (proxy :: k) ('[] :: [Type]) Source # 
Instance details

Defined in Data.HList.Record

type UnLabel (proxy :: k) ('[] :: [Type]) = '[] :: [k]
type UnLabel (proxy :: a) (Label x ': xs) Source # 
Instance details

Defined in Data.HList.Record

type UnLabel (proxy :: a) (Label x ': xs) = x ': UnLabel proxy xs

type family LabelsOf (ls :: [*]) :: [*] Source #

Construct the (phantom) list of labels of a record, or list of Label.

Instances

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

Defined in Data.HList.Record

type LabelsOf ('[] :: [Type]) = '[] :: [Type]
type LabelsOf (Label l ': r) Source # 
Instance details

Defined in Data.HList.Record

type LabelsOf (Label l ': r) = Label l ': LabelsOf r
type LabelsOf (Tagged l v ': r) Source # 
Instance details

Defined in Data.HList.Record

type LabelsOf (Tagged l v ': r) = Label l ': LabelsOf r

class HLabelSet' l1 l2 (leq :: Bool) r Source #

Instances

Instances details
Fail (DuplicatedLabel l1) => HLabelSet' (l1 :: k1) (l2 :: k2) 'True (r :: k3) Source # 
Instance details

Defined in Data.HList.Record

(HLabelSet (l2 ': r), HLabelSet (l1 ': r)) => HLabelSet' (l1 :: k) (l2 :: k) 'False (r :: [k]) Source # 
Instance details

Defined in Data.HList.Record

class HLabelSet ls Source #

Relation between HLabelSet and HRLabelSet

instance HLabelSet (LabelsOf ps) => HRLabelSet ps

see also HSet

Instances

Instances details
HLabelSet ('[] :: [k]) Source # 
Instance details

Defined in Data.HList.Record

(HEqK l1 l2 leq, HLabelSet' l1 l2 leq r) => HLabelSet (l1 ': (l2 ': r) :: [a]) Source # 
Instance details

Defined in Data.HList.Record

HLabelSet ('[x] :: [k]) Source # 
Instance details

Defined in Data.HList.Record

class (HLabelSet (LabelsOf ps), HAllTaggedLV ps) => HRLabelSet (ps :: [*]) Source #

Instances

Instances details
(HLabelSet (LabelsOf ps), HAllTaggedLV ps) => HRLabelSet ps Source # 
Instance details

Defined in Data.HList.Record

data DuplicatedLabel l Source #

Property of a proper label set for a record: no duplication of labels, and every element of the list is Tagged label value

data TaggedFn Source #

Constructors

TaggedFn 

Instances

Instances details
tx ~ Tagged t x => ApplyAB TaggedFn x tx Source # 
Instance details

Defined in Data.HList.Record

Methods

applyAB :: TaggedFn -> x -> tx Source #

class Relabeled r where Source #

Iso (Record s) (Record t) (Record a) (Record b), such that relabeled = unlabeled . from unlabeled

in other words, pretend a record has different labels, but the same values.

Methods

relabeled :: forall p f s t a b. (HMapTaggedFn (RecordValuesR s) a, HMapTaggedFn (RecordValuesR b) t, SameLengths '[s, a, t, b], RecordValuesR t ~ RecordValuesR b, RecordValuesR s ~ RecordValuesR a, RecordValues b, RecordValues s, Profunctor p, Functor f) => (r a `p` f (r b)) -> r s `p` f (r t) Source #

Instances

Instances details
Relabeled Record Source # 
Instance details

Defined in Data.HList.Record

Methods

relabeled :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (HMapTaggedFn (RecordValuesR s) a, HMapTaggedFn (RecordValuesR b) t, SameLengths '[s, a, t, b], RecordValuesR t ~ RecordValuesR b, RecordValuesR s ~ RecordValuesR a, RecordValues b, RecordValues s, Profunctor p, Functor f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

Relabeled Variant Source # 
Instance details

Defined in Data.HList.Variant

Methods

relabeled :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (HMapTaggedFn (RecordValuesR s) a, HMapTaggedFn (RecordValuesR b) t, SameLengths '[s, a, t, b], RecordValuesR t ~ RecordValuesR b, RecordValuesR s ~ RecordValuesR a, RecordValues b, RecordValues s, Profunctor p, Functor f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

newtype Record (r :: [*]) Source #

Constructors

Record (HList r) 

Instances

Instances details
Relabeled Record Source # 
Instance details

Defined in Data.HList.Record

Methods

relabeled :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (HMapTaggedFn (RecordValuesR s) a, HMapTaggedFn (RecordValuesR b) t, SameLengths '[s, a, t, b], RecordValuesR t ~ RecordValuesR b, RecordValuesR s ~ RecordValuesR a, RecordValues b, RecordValues s, Profunctor p, Functor f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

TypeIndexed Record TIP Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIP (TagR a)) (f (TIP (TagR b))) -> p (Record s) (f (Record t)) Source #

HMapAux HList (HFmap f) x y => HMapAux Record f x y Source # 
Instance details

Defined in Data.HList.Record

Methods

hMapAux :: f -> Record x -> Record y Source #

(HZipRecord x y xy, SameLengths '[x, y, xy]) => HUnzip Record x y xy Source # 
Instance details

Defined in Data.HList.Record

Methods

hUnzip :: Record xy -> (Record x, Record y) Source #

(HZipRecord x y xy, SameLengths '[x, y, xy]) => HZip Record x y xy Source #
>>> let x :: Record '[Tagged "x" Int]; x = undefined
>>> let y :: Record '[Tagged "x" Char]; y = undefined
>>> :t hZip x y
hZip x y :: Record '[Tagged "x" (Int, Char)]
Instance details

Defined in Data.HList.Record

Methods

hZip :: Record x -> Record y -> Record xy Source #

H2ProjectByLabels '[Label l] v t1 v' => HDeleteAtLabel Record (l :: k) v v' Source # 
Instance details

Defined in Data.HList.Record

Methods

hDeleteAtLabel :: Label l -> Record v -> Record v' Source #

(H2ProjectByLabels (LabelsOf a) s a_ _s_minus_a, HRLabelSet a_, HRLabelSet a, HRearrange (LabelsOf a) a_ a, HLeftUnion b s bs, HRLabelSet bs, HRearrange (LabelsOf t) bs t, HRLabelSet t) => Projected Record s t a b Source #
Lens rs rt ra rb

where rs ~ Record s, rt ~ Record t, ra ~ Record a, rb ~ Record b

Instance details

Defined in Data.HList.Labelable

Methods

projected :: forall (ty :: LabeledOpticType) p f. (ty ~ LabelableTy Record, LabeledOpticP ty p, LabeledOpticF ty f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

(HUpdateAtLabel2 l v r r', HasField l (Record r') v) => HUpdateAtLabel Record (l :: k) v r r' Source # 
Instance details

Defined in Data.HList.Record

Methods

hUpdateAtLabel :: Label l -> v -> Record r -> Record r' Source #

HLens x Record s t a b => Labelable (x :: k) Record s t a b Source #

make a Lens (Record s) (Record t) a b

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy Record :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x Record s t a b Source #

(t ~ (Any :: Type), Fail (FieldNotFound l ())) => HasField (l :: k) (Record ('[] :: [Type])) t Source #

XXX

Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel :: Label l -> Record '[] -> t Source #

(HEqK l l1 b, HasField' b l (Tagged l1 v1 ': r) v) => HasField (l :: k1) (Record (Tagged l1 v1 ': r)) v Source # 
Instance details

Defined in Data.HList.Record

Methods

hLookupByLabel :: Label l -> Record (Tagged l1 v1 ': r) -> v Source #

H2ProjectByLabels (LabelsOf r2) r1 r2 rout => SubType (Record r1 :: Type) (Record r2 :: Type) Source #

Subtyping for records

Instance details

Defined in Data.HList.Record

(HReverse l lRev, HMapTaggedFn lRev l') => HBuild' l (Record l') Source #

This instance allows creating a Record with

hBuild 3 a :: Record '[Tagged "x" Int, Tagged "y" Char]
Instance details

Defined in Data.HList.Record

Methods

hBuild' :: HList l -> Record l' Source #

HRLabelSet (t ': r) => HExtend t (Record r) Source # 
Instance details

Defined in Data.HList.Record

Associated Types

type HExtendR t (Record r) Source #

Methods

(.*.) :: t -> Record r -> HExtendR t (Record r) Source #

(HLeftUnion lv x lvx, HRLabelSet x, HLabelSet (LabelsOf x), HRearrange (LabelsOf x) lvx x) => HUpdateMany lv (Record x) Source #

implementation in terms of .<++.

Instance details

Defined in Data.HList.RecordU

Methods

hUpdateMany :: Record lv -> Record x -> Record x Source #

(HasField l (Record r) u, HasFieldPath needJust ls u v) => HasFieldPath needJust (Label l ': ls) (Record r) v Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Record r -> v Source #

TypeRepsList (HList xs) => TypeRepsList (Record xs) Source # 
Instance details

Defined in Data.HList.Data

Methods

typeRepsList :: Record xs -> [TypeRep] Source #

DataRecordCxt a => Data (Record a) Source # 
Instance details

Defined in Data.HList.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Record a -> c (Record a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Record a) #

toConstr :: Record a -> Constr #

dataTypeOf :: Record a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Record a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Record a)) #

gmapT :: (forall b. Data b => b -> b) -> Record a -> Record a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Record a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Record a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Record a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Record a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Record a -> m (Record a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Record a -> m (Record a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Record a -> m (Record a) #

Monoid (HList r) => Monoid (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

mempty :: Record r #

mappend :: Record r -> Record r -> Record r #

mconcat :: [Record r] -> Record r #

Semigroup (HList r) => Semigroup (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

(<>) :: Record r -> Record r -> Record r #

sconcat :: NonEmpty (Record r) -> Record r #

stimes :: Integral b => b -> Record r -> Record r #

Bounded (HList r) => Bounded (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

minBound :: Record r #

maxBound :: Record r #

Ix (HList r) => Ix (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

range :: (Record r, Record r) -> [Record r] #

index :: (Record r, Record r) -> Record r -> Int #

unsafeIndex :: (Record r, Record r) -> Record r -> Int #

inRange :: (Record r, Record r) -> Record r -> Bool #

rangeSize :: (Record r, Record r) -> Int #

unsafeRangeSize :: (Record r, Record r) -> Int #

(HMapCxt HList ReadComponent (AddProxy rs) bs, ApplyAB ReadComponent (Proxy r) readP_r, HProxies rs, HSequence ReadP (readP_r ': bs) (r ': rs), readP_r ~ ReadP (Tagged l v), r ~ Tagged l v, ShowLabel l, Read v, HSequence ReadP bs rs) => Read (Record (r ': rs)) Source # 
Instance details

Defined in Data.HList.Record

Methods

readsPrec :: Int -> ReadS (Record (r ': rs)) #

readList :: ReadS [Record (r ': rs)] #

readPrec :: ReadPrec (Record (r ': rs)) #

readListPrec :: ReadPrec [Record (r ': rs)] #

ShowComponents r => Show (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

showsPrec :: Int -> Record r -> ShowS #

show :: Record r -> String #

showList :: [Record r] -> ShowS #

Eq (HList r) => Eq (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

(==) :: Record r -> Record r -> Bool #

(/=) :: Record r -> Record r -> Bool #

Ord (HList r) => Ord (Record r) Source # 
Instance details

Defined in Data.HList.Record

Methods

compare :: Record r -> Record r -> Ordering #

(<) :: Record r -> Record r -> Bool #

(<=) :: Record r -> Record r -> Bool #

(>) :: Record r -> Record r -> Bool #

(>=) :: Record r -> Record r -> Bool #

max :: Record r -> Record r -> Record r #

min :: Record r -> Record r -> Record r #

(la ~ LabelsOf a, lt ~ LabelsOf t, HRearrange la s a, HRearrange lt b t, HLabelSet la, HLabelSet lt) => Rearranged Record (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]) Source #
Iso (Record s) (Record t) (Record a) (Record b)

where s is a permutation of a, b is a permutation of t. In practice sameLabels and sameLength are likely needed on both sides of rearranged, to avoid ambiguous types.

An alternative implementation:

rearranged x = iso hRearrange' hRearrange' x
Instance details

Defined in Data.HList.Record

Methods

rearranged :: (Profunctor p, Functor f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

(HRLabelSet (HAppendListR r1 r2), HAppend (HList r1) (HList r2)) => HAppend (Record r1) (Record r2) Source #
(.*.)
Add a field to a record. Analagous to (++) for lists.
record .*. field1
       .*. field2
Instance details

Defined in Data.HList.Record

Methods

hAppend :: Record r1 -> Record r2 -> HAppendR (Record r1) (Record r2) Source #

type LabelableTy Record Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR t (Record r) Source # 
Instance details

Defined in Data.HList.Record

type HExtendR t (Record r) = Record (t ': r)
type HAppendR (Record r1 :: Type) (Record r2 :: Type) Source # 
Instance details

Defined in Data.HList.Record

type HAppendR (Record r1 :: Type) (Record r2 :: Type) = Record (HAppendListR r1 r2)

labelLVPair :: Tagged l v -> Label l Source #

Label accessor

newLVPair :: Label l -> v -> Tagged l v Source #

(.=.) :: Label l -> v -> Tagged l v infixr 4 Source #

Create a value with the given label. Analagous to a data constructor such as Just, Left, or Right. Higher fixity than record-modification operations like (.*.), (.-.), etc. to support expression like the below w/o parentheses:

>>> x .=. "v1" .*. y .=. '2' .*. emptyRecord
Record{x="v1",y='2'}

mkRecord :: HRLabelSet r => HList r -> Record r Source #

Build a record

hListRecord :: forall {p} {f} {r1 :: [Type]} {r2 :: [Type]}. (Profunctor p, Functor f, HLabelSet (LabelsOf r1), HAllTaggedLV r1) => p (Record r1) (f (Record r2)) -> p (HList r1) (f (HList r2)) Source #

HRLabelSet t => Iso (HList s) (HList t) (Record s) (Record t)

hListRecord' :: forall {p} {f} {r :: [Type]}. (Profunctor p, Functor f, HLabelSet (LabelsOf r), HAllTaggedLV r) => p (Record r) (f (Record r)) -> p (HList r) (f (HList r)) Source #

Iso' (HList s) (Record s)

emptyRecord :: Record '[] Source #

Build an empty record

unlabeled0 :: forall {f} {p} {x :: [Type]} {y :: [Type]}. (Functor f, Profunctor p, SameLabels x y, HMapAux HList TaggedFn (RecordValuesR y) y, RecordValues x, RecordValues y) => p (HList (RecordValuesR x)) (f (HList (RecordValuesR y))) -> p (Record x) (f (Record y)) Source #

Iso (Record s) (Record t) (HList a) (HList b)
view unlabeled == recordValues

unlabeled :: (Unlabeled x y, Profunctor p, Functor f) => (HList (RecordValuesR x) `p` f (HList (RecordValuesR y))) -> Record x `p` f (Record y) Source #

unlabeled' :: (Unlabeled' x, Profunctor p, Functor f) => (HList (RecordValuesR x) `p` f (HList (RecordValuesR x))) -> Record x `p` f (Record x) Source #

Unlabeled' x => Iso' (Record x) (HList (RecordValuesR x))

relabeled' :: forall {t :: [Type]} {b :: [Type]} {r} {p} {f}. (RecordValuesR t ~ RecordValuesR b, Relabeled r, HMapAux HList TaggedFn (RecordValuesR t) b, HMapAux HList TaggedFn (RecordValuesR b) t, RecordValues b, RecordValues t, SameLength' t b, SameLength' t (RecordValuesR b), SameLength' b t, SameLength' b (RecordValuesR t), SameLength' (RecordValuesR t) b, SameLength' (RecordValuesR b) t, Profunctor p, Functor f) => p (r b) (f (r b)) -> p (r t) (f (r t)) Source #

Iso' (Record s) (Record a)

such that RecordValuesR s ~ RecordValuesR a

labelsOf :: hlistOrRecord l -> Proxy (LabelsOf l) Source #

(.!.) :: HasField l r v => r -> Label l -> v infixr 9 Source #

Lookup a value in a record by its label. Analagous to (!!), the list indexing operation. Highest fixity, like (!!).

>>> :{
let record1 = x .=. 3 .*.
              y .=. 'y' .*.
              emptyRecord
:}
>>> record1 .!. x
3
>>> record1 .!. y
'y'
>>> :{
let r2 = y .=. record1 .!. x .*.
         z .=. record1 .!. y .*.
         emptyRecord
:}
>>> r2
Record{y=3,z='y'}

Note that labels made following Data.HList.Labelable allow using "Control.Lens.^." instead.

(.-.) :: HDeleteAtLabel r l xs xs' => r xs -> Label l -> r xs' infixl 2 Source #

Remove a field from a record. At the same level as other record modification options (.*.). Analagous to (\\) in lists.

record1 .-. label1
label1 .=. value1 .*.
label2 .=. value2 .-.
label2 .*.
emptyRecord
label1 .=. value1 .-.
label1 .*.
label2 .=. value2 .*.
emptyRecord
record1 .*. label1 .=. record2 .!. label1
        .*. label2 .=. record2 .!. label2
        .-. label1

(.@.) :: forall {k} {record} {l :: k} {v} {r :: [Type]} {r' :: [Type]}. (HUpdateAtLabel record l v r r', SameLength' r r', SameLength' r' r) => Tagged l v -> record r -> record r' infixr 2 Source #

Update a field with a particular value. Same fixity as (.*.) so that extensions and updates can be chained. There is no real list analogue, since there is no Prelude defined update.

label1 .=. value1 .@. record1

hProjectByLabels :: (HRLabelSet a, H2ProjectByLabels ls t a b) => proxy ls -> Record t -> Record a Source #

hProjectByLabels ls r returns r with only the labels in ls remaining

hProjectByLabels' :: forall {l :: [Type]} {r :: [Type]} {t :: [Type]} {b :: [Type]}. (HRearrange3 (LabelsOf l) r l, SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r, HLabelSet (LabelsOf l), HLabelSet (LabelsOf r), HAllTaggedLV r, H2ProjectByLabels (LabelsOf l) t r b) => Record t -> Record l Source #

hRenameLabel :: forall {k1} {k2} {r} {l1 :: k1} {v1 :: [Type]} {v' :: [Type]} {v2} {l2 :: k2}. (HDeleteAtLabel r l1 v1 v', HasField l1 (r v1) v2, HExtend (Tagged l2 v2) (r v')) => Label l1 -> Label l2 -> r v1 -> HExtendR (Tagged l2 v2) (r v') Source #

Rename the label of record

>>> hRenameLabel x y (x .=. () .*. emptyRecord)
Record{y=()}

hTPupdateAtLabel :: HTPupdateAtLabel record l v r => Label l -> v -> record r -> record r Source #

We could also say:

hTPupdateAtLabel l v r = hUpdateAtLabel l v r `asTypeOf` r

Then we were taking a dependency on Haskell's type equivalence. This would also constrain the actual implementation of hUpdateAtLabel.

A variation on hUpdateAtLabel: type-preserving update.

(.<.) :: forall {k} {record} {l :: k} {v} {r :: [Type]}. (HUpdateAtLabel record l v r r, SameLength' r r) => Tagged l v -> record r -> record r infixr 2 Source #

The same as .@., except type preserving. It has the same fixity as (.@.).

(.<++.) :: HLeftUnion r r' r'' => Record r -> Record r' -> Record r'' infixl 1 Source #

Similar to list append, so give this slightly lower fixity than (.*.), so we can write:

field1 .=. value .*. record1 .<++. record2

hRearrange :: (HLabelSet ls, HRearrange ls r r') => Proxy ls -> Record r -> Record r' Source #

Rearranges a record by labels. Returns the record r, rearranged such that the labels are in the order given by ls. (LabelsOf r) must be a permutation of ls.

hRearrange' :: forall {l :: [Type]} {r :: [Type]}. (HLabelSet (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => Record r -> Record l Source #

hRearrange' is hRearrange where ordering specified by the Proxy argument is determined by the result type.

With built-in haskell records, these e1 and e2 have the same type:

data R = R { x, y :: Int }
e1 = R{ x = 1, y = 2}
e2 = R{ y = 2, x = 1}

hRearrange' can be used to allow either ordering to be accepted:

h1, h2 :: Record [ Tagged "x" Int, Tagged "y" Int ]
h1 = hRearrange' $
    x .=. 1 .*.
    y .=. 2 .*.
    emptyRecord

h2 = hRearrange' $
    y .=. 2 .*.
    x .=. 1 .*.
    emptyRecord

rearranged' :: forall {k} {r} {t :: k} {b :: k} {p} {f}. (Rearranged r t t b b, Profunctor p, Functor f) => p (r b) (f (r b)) -> p (r t) (f (r t)) Source #

Iso' (r s) (r a)

where s is a permutation of a

hMapR :: forall {x :: [Type]} {y :: [Type]} {f}. (SameLength' x y, SameLength' y x, HMapAux HList (HFmap f) x y) => f -> Record x -> Record y Source #

map over the values of a record. This is a shortcut for

\ f (Record a) -> Record (hMap (HFmap f) a)
Example

suppose we have a function that should be applied to every element of a record:

>>> let circSucc_ x | x == maxBound = minBound | otherwise = succ x
>>> :t circSucc_
circSucc_ :: (Bounded a, Enum a, Eq a) => a -> a

Use a shortcut (Fun) to create a value that has an appropriate ApplyAB instance:

>>> let circSucc = Fun circSucc_ :: Fun '[Eq,Enum,Bounded] '()

Confirm that we got Fun right:

>>> :t applyAB circSucc
applyAB circSucc :: (Bounded b, Enum b, Eq b) => b -> b
>>> applyAB circSucc True
False

define the actual record:

>>> let r = x .=. 'a' .*. y .=. False .*. emptyRecord
>>> r
Record{x='a',y=False}
>>> hMapR circSucc r
Record{x='b',y=True}

hEndR :: Record a -> Record a Source #

serves the same purpose as hEnd

hEndP :: Proxy (xs :: [k]) -> Proxy xs Source #

hEndP $ hBuild label1 label2

is one way to make a Proxy of labels (for use with asLabelsOf for example). Another way is

label1 .*. label2 .*. emptyProxy

zipTagged :: (MapLabel ts ~ lts, HZip Proxy lts vs tvs) => Proxy ts -> proxy vs -> Proxy tvs Source #

Missing from ghc-7.6, because HZip Proxy instances interfere with HZip HList instances.

a variation on hZip for Proxy, where the list of labels does not have to include Label (as in ts')

>>> let ts = Proxy :: Proxy ["x","y"]
>>> let ts' = Proxy :: Proxy [Label "x",Label "y"]
>>> let vs = Proxy :: Proxy [Int,Char]
>>> :t zipTagged ts Proxy
zipTagged ts Proxy :: Proxy '[Tagged "x" y, Tagged "y" y1]
>>> :t zipTagged ts vs
zipTagged ts vs :: Proxy '[Tagged "x" Int, Tagged "y" Char]

And and the case when hZip does the same thing:

>>> :t zipTagged ts' vs
zipTagged ts' vs :: Proxy '[Tagged "x" Int, Tagged "y" Char]
>>> :t hZip ts' vs
hZip ts' vs :: Proxy '[Tagged "x" Int, Tagged "y" Char]

hZipRecord2 :: forall {x :: [Type]} {y1 :: [Type]} {y2 :: [Type]}. (SameLabels x y1, SameLabels x y2, HAllTaggedLV x, HMapAux HList TaggedFn (RecordValuesR x) x, HZipList (RecordValuesR y1) (RecordValuesR y2) (RecordValuesR x), RecordValues x, RecordValues y1, RecordValues y2, SameLength' x y1, SameLength' x y2, SameLength' y2 x, SameLength' y1 x) => Record y1 -> Record y2 -> Record x Source #

instead of explicit recursion above, we could define HZipRecord in terms of HZipList. While all types are inferred, this implementation is probably slower, so explicit recursion is used in the HZip Record instance.

asLabelsOf :: (HAllTaggedLV x, SameLabels x y, SameLength x y) => r x -> s y -> r x Source #

similar to asTypeOf:

>>> let s0 = Proxy :: Proxy '["x", "y"]
>>> let s1 = Proxy :: Proxy '[Label "x", Label "y"]
>>> let s2 = Proxy :: Proxy '[Tagged "x" Int, Tagged "y" Char]
>>> let f0 r = () where _ = r `asLabelsOf` s0
>>> let f1 r = () where _ = r `asLabelsOf` s1
>>> let f2 r = () where _ = r `asLabelsOf` s2
>>> :t f0
f0 :: r '[Tagged "x" v, Tagged "y" v1] -> ()
>>> :t f1
f1 :: r '[Tagged "x" v, Tagged "y" v1] -> ()
>>> :t f2
f2 :: r '[Tagged "x" v, Tagged "y" v1] -> ()

pun :: QuasiQuoter Source #

requires labels to be promoted strings (kind Symbol), as provided by Data.HList.Label6 (ie. the label for foo is Label :: Label "foo"), or Data.HList.Labelable

class Kw (fn :: *) (arg_def :: [*]) r where Source #

kw takes a HList whose first element is a function, and the rest of the elements are default values. A useful trick is to have a final argument () which is not eaten up by a label (A only takes 1 argument). That way when you supply the () it knows there are no more arguments (?).

>>> data A = A
>>> instance IsKeyFN (A -> a -> b) True
>>> let f A a () = a + 1
>>> let f' = f .*. A .*. 1 .*. HNil
>>> kw f' A 0 ()
1
>>> kw f' ()
2

Methods

kw :: HList (fn ': arg_def) -> r Source #

Instances

Instances details
(KW' rflag fn akws arg_def r, akws ~ Arg kws ('[] :: [Type]), ReflectFK' flag fn kws, IsKeyFN r rflag, IsKeyFN fn flag) => Kw fn arg_def r Source # 
Instance details

Defined in Data.HList.Keyword

Methods

kw :: HList (fn ': arg_def) -> r Source #

data K s (c :: *) Source #

Instances

Instances details
r ~ (c -> b) => IsKeyFN (K s c -> r) 'True Source #

The purpose of this instance is to be able to use the same Symbol (type-level string) at different types. If they are supposed to be the same, then use Label instead of K

>>> let kA = K :: forall t. K "a" t
>>> let testF (K :: K "a" Int) a1 (K :: K "a" Integer) a2 () = a1-fromIntegral a2

therefore the following options works:

>>> kw (hBuild testF) kA (5 :: Int) kA (3 :: Integer) ()
2
>>> kw (hBuild testF) (K :: K "a" Integer) 3 (K :: K "a" Int) 5 ()
2

But you cannot leave off all Int or Integer annotations.

Instance details

Defined in Data.HList.Keyword

recToKW :: forall a b. (HMapCxt HList TaggedToKW a b, HConcat b) => Record a -> HList (HConcatR b) Source #

convert a Record into a list that can supply default arguments for kw

A bit of setup:

>>> :set -XQuasiQuotes
>>> import Data.HList.RecordPuns
>>> let f (_ :: Label "a") a (_ :: Label "b") b () = a `div` b
>>> let a = 2; b = 1; f' = f .*. recToKW [pun| a b |]
>>> kw f' ()
2
>>> kw f' (Label :: Label "a") 10 ()
10

data HZipF Source #

Constructors

HZipF 

Instances

Instances details
(HZip3 a b c, x ~ (HList a, HList b), y ~ HList c) => ApplyAB HZipF x y Source # 
Instance details

Defined in Data.HList.HZip

Methods

applyAB :: HZipF -> x -> y Source #

class HZip3 x y l | x y -> l, l -> x y where Source #

same as HZip but HCons the elements of x onto y. This might be doable as a hMap f (hZip x y), but that one doesn't propagate types as easily it seems.

Methods

hZip3 :: HList x -> HList y -> HList l Source #

Instances

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

Defined in Data.HList.HZip

Methods

hZip3 :: HList '[] -> HList '[] -> HList '[] Source #

(HList (x ': y) ~ z, HZip3 xs ys zs) => HZip3 (x ': xs) (HList y ': ys) (z ': zs) Source # 
Instance details

Defined in Data.HList.HZip

Methods

hZip3 :: HList (x ': xs) -> HList (HList y ': ys) -> HList (z ': zs) Source #

type family Snd a Source #

Instances

Instances details
type Snd (a, b) Source # 
Instance details

Defined in Data.HList.HZip

type Snd (a, b) = b

type family Fst a Source #

Instances

Instances details
type Fst (a, b) Source # 
Instance details

Defined in Data.HList.HZip

type Fst (a, b) = a

type family HZipR (x :: [*]) (y :: [*]) :: [*] Source #

calculates something like:

[a] -> [b] -> [(a,b)]

can be used to give another type for hZip2

hZip2 :: HList a -> HList b -> HList (HZipR a b)

Instances

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

Defined in Data.HList.HZip

type HZipR ('[] :: [Type]) ('[] :: [Type]) = '[] :: [Type]
type HZipR (x ': xs) (y ': ys) Source # 
Instance details

Defined in Data.HList.HZip

type HZipR (x ': xs) (y ': ys) = (x, y) ': HZipR xs ys

class HZipR (MapFst z) (MapSnd z) ~ z => HUnZip z where Source #

HZipR in the superclass constraint doesn't hurt, but it doesn't seem to be necessary

Associated Types

type MapFst z :: [*] Source #

type MapSnd z :: [*] Source #

Methods

hZip2 :: HList (MapFst z) -> HList (MapSnd z) -> HList z Source #

hUnzip2 :: HList z -> (HList (MapFst z), HList (MapSnd z)) Source #

Instances

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

Defined in Data.HList.HZip

Associated Types

type MapFst '[] :: [Type] Source #

type MapSnd '[] :: [Type] Source #

Methods

hZip2 :: HList (MapFst '[]) -> HList (MapSnd '[]) -> HList '[] Source #

hUnzip2 :: HList '[] -> (HList (MapFst '[]), HList (MapSnd '[])) Source #

(z ~ (x, y), HUnZip zs) => HUnZip (z ': zs) Source # 
Instance details

Defined in Data.HList.HZip

Associated Types

type MapFst (z ': zs) :: [Type] Source #

type MapSnd (z ': zs) :: [Type] Source #

Methods

hZip2 :: HList (MapFst (z ': zs)) -> HList (MapSnd (z ': zs)) -> HList (z ': zs) Source #

hUnzip2 :: HList (z ': zs) -> (HList (MapFst (z ': zs)), HList (MapSnd (z ': zs))) Source #

hTranspose :: forall {a :: [Type]} {b :: [Type]} {c :: [Type]} {es :: [Type]} {l :: [Type]} {n :: HNat}. (HZip3 a b c, HFoldr HZipF (HList es) l (HList b), HReplicateFD n (HList ('[] :: [Type])) es, SameLength' (HReplicateR n ()) a, HLengthEq1 a n, HLengthEq2 a n) => HList (HList a ': l) -> HList c Source #

this transpose requires equal-length HLists inside a HList:

>>> import Data.HList.HListPrelude
>>> let ex = (1 .*. 2 .*. HNil) .*. ('a' .*. 'b' .*. HNil) .*. ( 3 .*. 5 .*. HNil) .*. HNil

The original list:

>>> ex
H[H[1,2],H['a','b'],H[3,5]]

And transposed:

>>> hTranspose ex
H[H[1,'a',3],H[2,'b',5]]

class HEqByFn le => HAscList le (ps :: [*]) Source #

HAscList le xs confirms that xs is in ascending order, and reports which element is duplicated otherwise.

Instances

Instances details
(HEqByFn le, HAscList0 le ps ps) => HAscList (le :: k) ps Source # 
Instance details

Defined in Data.HList.HSort

class HEqByFn lt => HIsSetBy lt (ps :: [*]) (b :: Bool) | lt ps -> b Source #

Instances

Instances details
(HEqByFn lt, HSortBy lt ps ps', HIsAscList lt ps' b) => HIsSetBy (lt :: k) ps b Source # 
Instance details

Defined in Data.HList.HSort

class HIsSet (ps :: [*]) (b :: Bool) | ps -> b Source #

>>> let xx = Proxy :: HIsSet [Label "x", Label "x"] b => Proxy b
>>> :t xx
xx :: Proxy 'False
>>> let xy = Proxy :: HIsSet [Label "x", Label "y"] b => Proxy b
>>> :t xy
xy :: Proxy 'True

Instances

Instances details
HIsSetBy (HNeq HLeFn) ps b => HIsSet ps b Source # 
Instance details

Defined in Data.HList.HSort

class HSetBy (HNeq HLeFn) ps => HSet (ps :: [*]) Source #

Instances

Instances details
HSetBy (HNeq HLeFn) ps => HSet ps Source # 
Instance details

Defined in Data.HList.HSort

class HEqByFn lt => HSetBy lt (ps :: [*]) Source #

Provided the labels involved have an appropriate instance of HEqByFn, it would be possible to use the following definitions:

type HRLabelSet = HSet
type HLabelSet  = HSet

Instances

Instances details
(HEqByFn lt, HSortBy lt ps ps', HAscList lt ps') => HSetBy (lt :: k) ps Source # 
Instance details

Defined in Data.HList.HSort

type HSort x y = HSortBy HLeFn x y Source #

class (SameLength a b, HEqByFn le) => HSortBy le (a :: [*]) (b :: [*]) | le a -> b where Source #

quick sort with a special case for sorted lists

Methods

hSortBy :: Proxy le -> HList a -> HList b Source #

Instances

Instances details
(SameLength a b, HIsAscList le a ok, HSortBy1 ok le a b, HEqByFn le) => HSortBy (le :: k) a b Source # 
Instance details

Defined in Data.HList.HSort

Methods

hSortBy :: Proxy le -> HList a -> HList b Source #

class HEqByFn le => HIsAscList le (xs :: [*]) (b :: Bool) | le xs -> b Source #

HIsAscList le xs b is analogous to

b = all (\(x,y) -> x `le` y) (xs `zip` tail xs)

Instances

Instances details
HEqByFn le => HIsAscList (le :: k) ('[] :: [Type]) 'True Source # 
Instance details

Defined in Data.HList.HSort

(HEqBy le x y b1, HIsAscList le (y ': ys) b2, HAnd b1 b2 ~ b3) => HIsAscList (le :: k) (x ': (y ': ys)) b3 Source # 
Instance details

Defined in Data.HList.HSort

HEqByFn le => HIsAscList (le :: k) '[x] 'True Source # 
Instance details

Defined in Data.HList.HSort

data HDown a Source #

analogous to Down

Instances

Instances details
HEqBy f y x b => HEqBy (HDown f :: Type) (x :: k2) (y :: k2) b Source # 
Instance details

Defined in Data.HList.HSort

HEqByFn a => HEqByFn (HDown a :: Type) Source # 
Instance details

Defined in Data.HList.HSort

data HLeFn Source #

the "standard" <= for types. Reuses HEqBy

Note that ghc-7.6 is missing instances for Symbol and Nat, so that sorting only works HNat (as used by Data.HList.Label3).

Instances

Instances details
HEqByFn HLeFn Source # 
Instance details

Defined in Data.HList.HSort

HLe x y ~ b => HEqBy HLeFn (x :: HNat) (y :: HNat) b Source # 
Instance details

Defined in Data.HList.HSort

(HEq (CmpSymbol x y) 'GT nb, HNot nb ~ b) => HEqBy HLeFn (x :: Symbol) (y :: Symbol) b Source #

only in ghc >= 7.7

>>> let b1 = Proxy :: HEqBy HLeFn "x" "y" b => Proxy b
>>> :t b1
b1 :: Proxy 'True
>>> let b2 = Proxy :: HEqBy HLeFn "x" "x" b => Proxy b
>>> :t b2
b2 :: Proxy 'True
>>> let b3 = Proxy :: HEqBy HLeFn "y" "x" b => Proxy b
>>> :t b3
b3 :: Proxy 'False
Instance details

Defined in Data.HList.HSort

(x <=? y) ~ b => HEqBy HLeFn (x :: k) (y :: k) b Source #

only in ghc >= 7.7

Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Label x :: Type) (Label y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Proxy x :: Type) (Proxy y :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

(HEqBy HLeFn n m b, ns ~ ns') => HEqBy HLeFn (Lbl n ns desc :: Type) (Lbl m ns' desc' :: Type) b Source #

Data.HList.Label3 labels can only be compared if they belong to the same namespace.

Instance details

Defined in Data.HList.HSort

HEqBy HLeFn x y b => HEqBy HLeFn (Tagged x v :: Type) (Tagged y w :: Type) b Source # 
Instance details

Defined in Data.HList.HSort

hSort :: HSort x y => HList x -> HList y Source #

class HOccursNot2 (b :: Bool) e (l :: [k]) (l0 :: [k]) Source #

Instances

Instances details
HOccursNot1 e l l0 => HOccursNot2 'False (e :: k) (l :: [k]) (l0 :: [k]) Source # 
Instance details

Defined in Data.HList.HOccurs

Fail (ExcessFieldFound e l0) => HOccursNot2 'True (e :: k1) (l :: [k2]) (l0 :: [k2]) Source # 
Instance details

Defined in Data.HList.HOccurs

class HOccursNot1 (e :: k) (xs :: [k]) (xs0 :: [k]) Source #

Instances

Instances details
HOccursNot1 (e :: k) ('[] :: [k]) (l0 :: [k]) Source # 
Instance details

Defined in Data.HList.HOccurs

(HEq e e1 b, HOccursNot2 b e l l0) => HOccursNot1 (e :: a) (e1 ': l :: [a]) (l0 :: [a]) Source # 
Instance details

Defined in Data.HList.HOccurs

class HOccursOpt' e l where Source #

Methods

hOccursOpt' :: HList l -> Maybe e Source #

Instances

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

Defined in Data.HList.HOccurs

Methods

hOccursOpt' :: HList '[] -> Maybe e Source #

e ~ e1 => HOccursOpt' e (e1 ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursOpt' :: HList (e1 ': l) -> Maybe e Source #

class HOccurs' e l (l0 :: [*]) where Source #

l0 is the original list so that when we reach the end of l without finding an e, we can report an error that gives an idea about what the original list was.

Methods

hOccurs' :: Proxy l0 -> HList l -> e Source #

Instances

Instances details
Fail (FieldNotFound e (HList l0)) => HOccurs' e ('[] :: [Type]) l0 Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs' :: Proxy l0 -> HList '[] -> e Source #

HOccursNot e l => HOccurs' e (e ': l) l0 Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurs' :: Proxy l0 -> HList (e ': l) -> e Source #

class HOccursMany' e l where Source #

Methods

hOccursMany' :: HList l -> [e] Source #

Instances

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

Defined in Data.HList.HOccurs

Methods

hOccursMany' :: HList '[] -> [e] Source #

(e ~ e1, HOccursMany e l) => HOccursMany' e (e1 ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursMany' :: HList (e1 ': l) -> [e] Source #

class HOccursMany e (l :: [*]) where Source #

Methods

hOccursMany :: HList l -> [e] Source #

Instances

Instances details
(HOccurrence e l l', HOccursMany' e l') => HOccursMany e l Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccursMany :: HList l -> [e] Source #

class HOccurrence' (b :: Bool) (e1 :: *) (l :: [*]) (l' :: [*]) | b e1 l -> l' where Source #

Methods

hOccurrence' :: Proxy b -> Proxy e1 -> HList l -> HList l' Source #

Instances

Instances details
HOccurrence e1 l l' => HOccurrence' 'False e1 (e ': l) l' Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurrence' :: Proxy 'False -> Proxy e1 -> HList (e ': l) -> HList l' Source #

HOccurrence' 'True e1 (e ': l) (e ': l) Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurrence' :: Proxy 'True -> Proxy e1 -> HList (e ': l) -> HList (e ': l) Source #

class HOccurrence (e1 :: *) (l :: [*]) (l' :: [*]) | e1 l -> l' where Source #

Methods

hOccurrence :: Proxy e1 -> HList l -> HList l' Source #

Instances

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

Defined in Data.HList.HOccurs

Methods

hOccurrence :: Proxy e1 -> HList '[] -> HList '[] Source #

(HEq e1 e b, HOccurrence' b e1 (e ': l) l') => HOccurrence e1 (e ': l) l' Source # 
Instance details

Defined in Data.HList.HOccurs

Methods

hOccurrence :: Proxy e1 -> HList (e ': l) -> HList l' Source #

hOccursMany1 :: forall e l l'. (HOccurrence e l (e ': l'), HOccursMany e l') => HList l -> (e, [e]) Source #

hOccursFst :: forall e l l'. HOccurrence e l (e ': l') => HList l -> e Source #

hOccursRest :: forall {l} {r} {v :: [Type]} {v' :: [Type]}. (HOccurs l (r v), HDeleteAtLabel r l v v') => r v -> (l, r v') Source #

lookup a value in the collection (TIP usually) and return the TIP with that element deleted. Used to implement tipyTuple.

hOccursOpt :: forall e l l'. (HOccurrence e l l', HOccursOpt' e l') => HList l -> Maybe e Source #

tipyTuple :: forall {t1} {r} {v1 :: [Type]} {v2 :: [Type]} {t2} {v3 :: [Type]} {v'1 :: [Type]} {v'2 :: [Type]}. (HOccurs t1 (r v1), HOccurs t1 (r v2), HOccurs t2 (r v2), HOccurs t2 (r v3), HDeleteAtLabel r t1 v1 v'1, HDeleteAtLabel r t1 v2 v3, HDeleteAtLabel r t2 v2 v1, HDeleteAtLabel r t2 v3 v'2) => r v2 -> (t2, t1) Source #

project a TIP (or HList) into a tuple

tipyTuple' x = (hOccurs x, hOccurs x)

behaves similarly, except tipyTuple excludes the possibility of looking up the same element twice, which allows inferring a concrete type in more situations. For example

(\x y z -> tipyTuple (x .*. y .*. emptyTIP) `asTypeOf` (x, z)) () 'x'

has type Char -> ((), Char). tipyTuple' would need a type annotation to decide whether the type should be Char -> ((), Char) or () -> ((), ())

tipyTuple3 :: forall {t1} {r} {v1 :: [Type]} {v2 :: [Type]} {v3 :: [Type]} {t2} {v4 :: [Type]} {v5 :: [Type]} {t3} {v6 :: [Type]} {v7 :: [Type]} {v'1 :: [Type]} {v'2 :: [Type]} {v'3 :: [Type]}. (HOccurs t1 (r v1), HOccurs t1 (r v2), HOccurs t1 (r v3), HOccurs t2 (r v4), HOccurs t2 (r v3), HOccurs t2 (r v5), HOccurs t3 (r v3), HOccurs t3 (r v6), HOccurs t3 (r v7), HDeleteAtLabel r t1 v1 v4, HDeleteAtLabel r t1 v2 v'1, HDeleteAtLabel r t1 v3 v5, HDeleteAtLabel r t2 v4 v'2, HDeleteAtLabel r t2 v3 v6, HDeleteAtLabel r t2 v5 v7, HDeleteAtLabel r t3 v3 v1, HDeleteAtLabel r t3 v6 v2, HDeleteAtLabel r t3 v7 v'3) => r v3 -> (t3, t1, t2) Source #

tipyTuple4 :: forall {t1} {r} {v1 :: [Type]} {v2 :: [Type]} {v3 :: [Type]} {v4 :: [Type]} {t2} {v5 :: [Type]} {v6 :: [Type]} {v7 :: [Type]} {t3} {v8 :: [Type]} {v9 :: [Type]} {v10 :: [Type]} {t4} {v11 :: [Type]} {v12 :: [Type]} {v13 :: [Type]} {v'1 :: [Type]} {v'2 :: [Type]} {v'3 :: [Type]} {v'4 :: [Type]}. (HOccurs t1 (r v1), HOccurs t1 (r v2), HOccurs t1 (r v3), HOccurs t1 (r v4), HOccurs t2 (r v5), HOccurs t2 (r v6), HOccurs t2 (r v4), HOccurs t2 (r v7), HOccurs t3 (r v8), HOccurs t3 (r v4), HOccurs t3 (r v9), HOccurs t3 (r v10), HOccurs t4 (r v4), HOccurs t4 (r v11), HOccurs t4 (r v12), HOccurs t4 (r v13), HDeleteAtLabel r t1 v1 v5, HDeleteAtLabel r t1 v2 v6, HDeleteAtLabel r t1 v3 v'1, HDeleteAtLabel r t1 v4 v7, HDeleteAtLabel r t2 v5 v8, HDeleteAtLabel r t2 v6 v'2, HDeleteAtLabel r t2 v4 v9, HDeleteAtLabel r t2 v7 v10, HDeleteAtLabel r t3 v8 v'3, HDeleteAtLabel r t3 v4 v11, HDeleteAtLabel r t3 v9 v12, HDeleteAtLabel r t3 v10 v13, HDeleteAtLabel r t4 v4 v1, HDeleteAtLabel r t4 v11 v2, HDeleteAtLabel r t4 v12 v3, HDeleteAtLabel r t4 v13 v'4) => r v4 -> (t4, t1, t2, t3) Source #

tipyTuple5 :: forall {t1} {r} {v1 :: [Type]} {v2 :: [Type]} {v3 :: [Type]} {v4 :: [Type]} {v5 :: [Type]} {t2} {v6 :: [Type]} {v7 :: [Type]} {v8 :: [Type]} {v9 :: [Type]} {t3} {v10 :: [Type]} {v11 :: [Type]} {v12 :: [Type]} {v13 :: [Type]} {t4} {v14 :: [Type]} {v15 :: [Type]} {v16 :: [Type]} {v17 :: [Type]} {t5} {v18 :: [Type]} {v19 :: [Type]} {v20 :: [Type]} {v21 :: [Type]} {v'1 :: [Type]} {v'2 :: [Type]} {v'3 :: [Type]} {v'4 :: [Type]} {v'5 :: [Type]}. (HOccurs t1 (r v1), HOccurs t1 (r v2), HOccurs t1 (r v3), HOccurs t1 (r v4), HOccurs t1 (r v5), HOccurs t2 (r v6), HOccurs t2 (r v7), HOccurs t2 (r v8), HOccurs t2 (r v5), HOccurs t2 (r v9), HOccurs t3 (r v10), HOccurs t3 (r v11), HOccurs t3 (r v5), HOccurs t3 (r v12), HOccurs t3 (r v13), HOccurs t4 (r v14), HOccurs t4 (r v5), HOccurs t4 (r v15), HOccurs t4 (r v16), HOccurs t4 (r v17), HOccurs t5 (r v5), HOccurs t5 (r v18), HOccurs t5 (r v19), HOccurs t5 (r v20), HOccurs t5 (r v21), HDeleteAtLabel r t1 v1 v6, HDeleteAtLabel r t1 v2 v7, HDeleteAtLabel r t1 v3 v8, HDeleteAtLabel r t1 v4 v'1, HDeleteAtLabel r t1 v5 v9, HDeleteAtLabel r t2 v6 v10, HDeleteAtLabel r t2 v7 v11, HDeleteAtLabel r t2 v8 v'2, HDeleteAtLabel r t2 v5 v12, HDeleteAtLabel r t2 v9 v13, HDeleteAtLabel r t3 v10 v14, HDeleteAtLabel r t3 v11 v'3, HDeleteAtLabel r t3 v5 v15, HDeleteAtLabel r t3 v12 v16, HDeleteAtLabel r t3 v13 v17, HDeleteAtLabel r t4 v14 v'4, HDeleteAtLabel r t4 v5 v18, HDeleteAtLabel r t4 v15 v19, HDeleteAtLabel r t4 v16 v20, HDeleteAtLabel r t4 v17 v21, HDeleteAtLabel r t5 v5 v1, HDeleteAtLabel r t5 v18 v2, HDeleteAtLabel r t5 v19 v3, HDeleteAtLabel r t5 v20 v4, HDeleteAtLabel r t5 v21 v'5) => r v5 -> (t5, t1, t2, t3, t4) Source #

class HLengthEq xs n => HCurry' (n :: HNat) f xs r | f xs -> r, r xs -> f, n f -> xs, xs -> n where Source #

curry/uncurry for many arguments and HLists instead of tuples

XXX the last FD xs -> n is needed to make hCompose infer the right types: arguably it shouldn't be needed

Methods

hUncurry' :: Proxy n -> f -> HList xs -> r Source #

hCurry' :: Proxy n -> (HList xs -> r) -> f Source #

Instances

Instances details
HCurry' 'HZero b ('[] :: [Type]) b Source # 
Instance details

Defined in Data.HList.HCurry

Methods

hUncurry' :: Proxy 'HZero -> b -> HList '[] -> b Source #

hCurry' :: Proxy 'HZero -> (HList '[] -> b) -> b Source #

HCurry' n b xs r => HCurry' ('HSucc n) (x -> b) (x ': xs) r Source # 
Instance details

Defined in Data.HList.HCurry

Methods

hUncurry' :: Proxy ('HSucc n) -> (x -> b) -> HList (x ': xs) -> r Source #

hCurry' :: Proxy ('HSucc n) -> (HList (x ': xs) -> r) -> x -> b Source #

hUncurry :: forall {n :: HNat} {f} {xs :: [Type]} {r}. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => f -> HList xs -> r Source #

hCurry :: forall {n :: HNat} {f} {xs :: [Type]} {r}. (HCurry' n f xs r, ArityFwd f n, ArityRev f n) => (HList xs -> r) -> f Source #

Note: with ghc-7.10 the Arity constraint added here does not work properly with hCompose, so it is possible that other uses of hCurry are better served by hCurry' Proxy.

hCompose :: forall {f1} {n1 :: HNat} {b} {n2 :: HNat} {xs1 :: [Type]} {x} {xs2 :: [Type]} {r} {n3 :: HNat} {f2} {xsys :: [Type]}. (ArityRev f1 n1, ArityRev b n2, ArityFwd f1 n1, ArityFwd b n2, HCurry' n1 f1 xs1 x, HCurry' n2 b xs2 r, HCurry' n3 f2 xsys r, HAppendList1 xs1 xs2 xsys, HSplitAt1 ('[] :: [Type]) n1 xsys xs1 xs2) => (x -> b) -> f1 -> f2 Source #

compose two functions that take multiple arguments. The result of the second function is the first argument to the first function. An example is probably clearer:

>>> let f = hCompose (,,) (,)
>>> :t f
f :: ... -> ... -> ... -> ... -> ((..., ...), ..., ...)
>>> f 1 2 3 4
((1,2),3,4)

Note: polymorphism can make it confusing as to how many parameters a function actually takes. For example, the first two ids are id :: (a -> b) -> (a -> b) in

>>> (.) id id id 'y'
'y'
>>> hCompose id id id 'y'
'y'

still typechecks, but in that case hCompose i1 i2 i3 x == i1 ((i2 i3) x) has id with different types than @(.) i1 i2 i3 x == (i1 (i2 i3)) x

Prompted by http://stackoverflow.com/questions/28932054/can-hlistelim-be-composed-with-another-function

type HProjectAwayByHNatsR (ns :: [HNat]) (l :: [*]) = HUnfold (FHUProj False ns) (HList l, Proxy 'HZero) Source #

type HProjectByHNatsR (ns :: [HNat]) (l :: [*]) = HUnfold (FHUProj True ns) (HList l, Proxy 'HZero) Source #

type family KMember (n :: HNat) (ns :: [HNat]) :: Bool Source #

Instances

Instances details
type KMember n ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.HArray

type KMember n ('[] :: [HNat]) = 'False
type KMember n (n1 ': l) Source # 
Instance details

Defined in Data.HList.HArray

type KMember n (n1 ': l) = HOr (HNatEq n n1) (KMember n l)

data FHUProj (sel :: Bool) (ns :: [HNat]) Source #

Constructors

FHUProj 

Instances

Instances details
(ch ~ Proxy (HBoolEQ sel (KMember n ns)), Apply (ch, FHUProj sel ns) (HList (e ': l), Proxy n)) => Apply (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: FHUProj sel ns -> (HList (e ': l), Proxy n) -> ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (FHUProj sel ns) (HList ('[] :: [Type]), n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHUProj sel ns) (HList '[], n) Source #

Methods

apply :: FHUProj sel ns -> (HList '[], n) -> ApplyR (FHUProj sel ns) (HList '[], n) Source #

Apply (FHUProj sel ns) (HList l, Proxy ('HSucc n)) => Apply (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'False, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Apply (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

Methods

apply :: (Proxy 'True, FHUProj sel ns) -> (HList (e ': l), Proxy n) -> ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source #

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (Proxy (HBoolEQ sel (KMember n ns)), FHUProj sel ns) (HList (e ': l), Proxy n)
type ApplyR (FHUProj sel ns) (HList ('[] :: [Type]), n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (FHUProj sel ns) (HList ('[] :: [Type]), n) = HNothing
type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'False, FHUProj sel ns) (HList (e ': l), Proxy n) = ApplyR (FHUProj sel ns) (HList l, Proxy ('HSucc n))
type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

type ApplyR (Proxy 'True, FHUProj sel ns) (HList (e ': l), Proxy n) = HJust (e, (HList l, Proxy ('HSucc n)))

newtype FHLookupByHNat (l :: [*]) Source #

Constructors

FHLookupByHNat (HList l) 

Instances

Instances details
HLookupByHNat n l => Apply (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type ApplyR (FHLookupByHNat l) (Proxy n) Source #

type ApplyR (FHLookupByHNat l) (Proxy n) Source # 
Instance details

Defined in Data.HList.HArray

class HUpdateAtHNat' (n :: HNat) e (l :: [*]) (l0 :: [*]) where Source #

Associated Types

type HUpdateAtHNatR (n :: HNat) e (l :: [*]) :: [*] Source #

Methods

hUpdateAtHNat' :: Proxy l0 -> Proxy n -> e -> HList l -> HList (HUpdateAtHNatR n e l) Source #

Instances

Instances details
Fail (HNatIndexTooLarge n HList l0) => HUpdateAtHNat' n e1 ('[] :: [Type]) l0 Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HUpdateAtHNatR n e1 '[] :: [Type] Source #

Methods

hUpdateAtHNat' :: Proxy l0 -> Proxy n -> e1 -> HList '[] -> HList (HUpdateAtHNatR n e1 '[]) Source #

HUpdateAtHNat' 'HZero e1 (e ': l) l0 Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HUpdateAtHNatR 'HZero e1 (e ': l) :: [Type] Source #

Methods

hUpdateAtHNat' :: Proxy l0 -> Proxy 'HZero -> e1 -> HList (e ': l) -> HList (HUpdateAtHNatR 'HZero e1 (e ': l)) Source #

HUpdateAtHNat' n e1 l l0 => HUpdateAtHNat' ('HSucc n) e1 (e ': l) l0 Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HUpdateAtHNatR ('HSucc n) e1 (e ': l) :: [Type] Source #

Methods

hUpdateAtHNat' :: Proxy l0 -> Proxy ('HSucc n) -> e1 -> HList (e ': l) -> HList (HUpdateAtHNatR ('HSucc n) e1 (e ': l)) Source #

class HUpdateAtHNat' n e l l => HUpdateAtHNat n e l where Source #

Methods

hUpdateAtHNat :: Proxy n -> e -> HList l -> HList (HUpdateAtHNatR n e l) Source #

Instances

Instances details
HUpdateAtHNat' n e l l => HUpdateAtHNat n e l Source # 
Instance details

Defined in Data.HList.HArray

Methods

hUpdateAtHNat :: Proxy n -> e -> HList l -> HList (HUpdateAtHNatR n e l) Source #

class HDeleteAtHNat (n :: HNat) (l :: [*]) where Source #

Associated Types

type HDeleteAtHNatR (n :: HNat) (l :: [*]) :: [*] Source #

Instances

Instances details
HDeleteAtHNat 'HZero (e ': l) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HDeleteAtHNatR 'HZero (e ': l) :: [Type] Source #

Methods

hDeleteAtHNat :: Proxy 'HZero -> HList (e ': l) -> HList (HDeleteAtHNatR 'HZero (e ': l)) Source #

HDeleteAtHNat n l => HDeleteAtHNat ('HSucc n) (e ': l) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HDeleteAtHNatR ('HSucc n) (e ': l) :: [Type] Source #

Methods

hDeleteAtHNat :: Proxy ('HSucc n) -> HList (e ': l) -> HList (HDeleteAtHNatR ('HSucc n) (e ': l)) Source #

class HLookupByHNat (n :: HNat) (l :: [*]) where Source #

Associated Types

type HLookupByHNatR (n :: HNat) (l :: [*]) :: * Source #

Instances

Instances details
HLookupByHNat 'HZero (e ': l) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HLookupByHNatR 'HZero (e ': l) Source #

Methods

hLookupByHNat :: Proxy 'HZero -> HList (e ': l) -> HLookupByHNatR 'HZero (e ': l) Source #

HLookupByHNat n l => HLookupByHNat ('HSucc n) (e ': l) Source # 
Instance details

Defined in Data.HList.HArray

Associated Types

type HLookupByHNatR ('HSucc n) (e ': l) Source #

Methods

hLookupByHNat :: Proxy ('HSucc n) -> HList (e ': l) -> HLookupByHNatR ('HSucc n) (e ': l) Source #

hProjectByHNats' :: forall {a :: [Type]} {b :: [Type]} {r} {l :: [Type]}. (SameLength' a b, SameLength' b a, HMapAux r (FHLookupByHNat l) a b) => r a -> HList l -> r b Source #

hProjectByHNats :: forall {ns :: [HNat]} {a} {z :: [Type]}. (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (a, Proxy 'HZero)) z, Apply (FHUProj 'True ns) (a, Proxy 'HZero)) => Proxy ns -> a -> HList z Source #

hProjectAwayByHNats :: forall {ns :: [HNat]} {a} {z :: [Type]}. (HUnfoldFD (FHUProj 'False ns) (ApplyR (FHUProj 'False ns) (a, Proxy 'HZero)) z, Apply (FHUProj 'False ns) (a, Proxy 'HZero)) => Proxy ns -> a -> HList z Source #

hSplitByHNats :: forall {ns :: [HNat]} {a} {z1 :: [Type]} {z2 :: [Type]}. (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (a, Proxy 'HZero)) z1, HUnfoldFD (FHUProj 'False ns) (ApplyR (FHUProj 'False ns) (a, Proxy 'HZero)) z2, Apply (FHUProj 'True ns) (a, Proxy 'HZero), Apply (FHUProj 'False ns) (a, Proxy 'HZero)) => Proxy ns -> a -> (HList z1, HList z2) Source #

Splitting an array according to indices

data HMaybiedToVariantFs Source #

Instances

Instances details
(x ~ (Tagged t (Maybe e), [Variant v]), y ~ [Variant (Tagged t e ': v)], MkVariant t e (Tagged t e ': v)) => ApplyAB HMaybiedToVariantFs x y Source # 
Instance details

Defined in Data.HList.Variant

Methods

applyAB :: HMaybiedToVariantFs -> x -> y Source #

class VariantToHMaybied v r | v -> r, r -> v where Source #

Instances

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

Defined in Data.HList.Variant

Methods

variantToHMaybied :: Variant '[] -> Record '[] Source #

(VariantToHMaybied v r, HReplicateF nr ConstTaggedNothing () r, tx ~ Tagged t x, tmx ~ Tagged t (Maybe x)) => VariantToHMaybied (tx ': v) (tmx ': r) Source # 
Instance details

Defined in Data.HList.Variant

Methods

variantToHMaybied :: Variant (tx ': v) -> Record (tmx ': r) Source #

class (HAllTaggedLV y, HAllTaggedLV x) => ExtendsVariant x y where Source #

projectVariant . extendsVariant = Just (when the types match up)

extendVariant is a special case

Instances

Instances details
(MkVariant l e y, le ~ Tagged l e, ExtendsVariant (b ': bs) y) => ExtendsVariant (le ': (b ': bs)) y Source # 
Instance details

Defined in Data.HList.Variant

Methods

extendsVariant :: Variant (le ': (b ': bs)) -> Variant y Source #

(HAllTaggedLV x, Unvariant '[le] e, MkVariant l e x, le ~ Tagged l e) => ExtendsVariant '[le] x Source # 
Instance details

Defined in Data.HList.Variant

Methods

extendsVariant :: Variant '[le] -> Variant x Source #

class (ProjectVariant x yin, ProjectVariant x yout) => SplitVariant x yin yout where Source #

Methods

splitVariant :: Variant x -> Either (Variant yin) (Variant yout) Source #

Instances

Instances details
(ProjectVariant x yin, ProjectVariant x yout, H2ProjectByLabels (LabelsOf yin) x xi xo, HRearrange (LabelsOf yin) xi yin, HRearrange (LabelsOf yout) xo yout, HLeftUnion xi xo xixo, HRearrange (LabelsOf x) xixo x, HAllTaggedLV x, HAllTaggedLV yin, HAllTaggedLV yout) => SplitVariant x yin yout Source # 
Instance details

Defined in Data.HList.Variant

Methods

splitVariant :: Variant x -> Either (Variant yin) (Variant yout) Source #

class HAllTaggedLV y => ProjectExtendVariant x y where Source #

projectExtendVariant = fmap extendVariant . projectVariant

where intermediate variant is as large as possible. Used to implement Data.HList.Labelable.projected

Note that:

>>> let r = projectExtendVariant (mkVariant1 Label 1 :: Variant '[Tagged "x" Int])
>>> r :: Maybe (Variant '[Tagged "x" Integer])
Nothing

Instances

Instances details
HAllTaggedLV y => ProjectExtendVariant ('[] :: [Type]) y Source # 
Instance details

Defined in Data.HList.Variant

(lv ~ Tagged l v, HMemberM lv y inY, ProjectExtendVariant' inY lv y, ProjectExtendVariant xs y) => ProjectExtendVariant (lv ': xs) y Source # 
Instance details

Defined in Data.HList.Variant

Methods

projectExtendVariant :: Variant (lv ': xs) -> Maybe (Variant y) Source #

class ProjectVariant x y where Source #

convert a variant with more fields into one with fewer (or the same) fields.

>>> let ty = Proxy :: Proxy [Tagged "left" Int, Tagged "right" Int]
>>> let l = mkVariant _left 1 ty
>>> let r = mkVariant _right 2 ty
>>> map projectVariant [l, r] :: [Maybe (Variant '[Tagged "left" Int])]
[Just V{left=1},Nothing]

rearrangeVariant = fromJust . projectVariant is one implementation of rearrangeVariant, since the result can have the same fields with a different order:

>>> let yt = Proxy :: Proxy [Tagged "right" Int, Tagged "left" Int]
>>> map projectVariant [l, r] `asTypeOf` [Just (mkVariant _left 0 yt)]
[Just V{left=1},Just V{right=2}]

Instances

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

Defined in Data.HList.Variant

(ProjectVariant x ys, HasField t (Variant x) (Maybe y), HOccursNot (Label t) (LabelsOf ys), ty ~ Tagged t y) => ProjectVariant x (ty ': ys) Source # 
Instance details

Defined in Data.HList.Variant

Methods

projectVariant :: Variant x -> Maybe (Variant (ty ': ys)) Source #

class (SameLength v v', SameLabels v v') => ZipVR fs v v' | fs v -> v' where Source #

Apply a record of functions to a variant of values. The functions are selected based on those having the same label as the value.

Methods

zipVR_ :: Record fs -> Variant v -> Variant v' Source #

zipVR is probably a better choice in most situations, since it requires that fs has one function for every element of v

Instances

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

Defined in Data.HList.Variant

Methods

zipVR_ :: Record fs -> Variant '[] -> Variant '[] Source #

(lv ~ Tagged l v, lv' ~ Tagged l v', HMemberM (Label l) (LabelsOf fs) b, HasFieldM l (Record fs) f, DemoteMaybe (v -> v) f ~ (v -> v'), MkVariant l v' (lv' ': rs), ZipVR fs vs rs) => ZipVR fs (lv ': vs) (lv' ': rs) Source # 
Instance details

Defined in Data.HList.Variant

Methods

zipVR_ :: Record fs -> Variant (lv ': vs) -> Variant (lv' ': rs) Source #

class ZipVariant x y xy | x y -> xy, xy -> x y where Source #

Applies to variants that have the same labels in the same order. A generalization of

zipEither :: Either a b -> Either a b -> Maybe (Either (a,a) (b,b))
zipEither (Left a) (Left a') = Just (Left (a,a'))
zipEither (Right a) (Right a') = Just (Right (a,a'))
zipEither _ _ = Nothing

see HZip for zipping other collections

Methods

zipVariant :: Variant x -> Variant y -> Maybe (Variant xy) Source #

Instances

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

Defined in Data.HList.Variant

Methods

zipVariant :: Variant '[] -> Variant '[] -> Maybe (Variant '[]) Source #

(tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y), ZipVariant xs ys zs, MkVariant t (x, y) (txy ': zs)) => ZipVariant (tx ': xs) (ty ': ys) (txy ': zs) Source # 
Instance details

Defined in Data.HList.Variant

Methods

zipVariant :: Variant (tx ': xs) -> Variant (ty ': ys) -> Maybe (Variant (txy ': zs)) Source #

class Unvariant v e | v -> e where Source #

Convert a Variant which has all possibilities having the same type into a value of that type. Analogous to either id id.

See also unvariant'

Methods

unvariant :: Variant v -> e Source #

Instances

Instances details
(Unvariant1 b v e, HAllEqVal v b, HAllEqVal (Tagged () e ': v) b) => Unvariant v e Source # 
Instance details

Defined in Data.HList.Variant

Methods

unvariant :: Variant v -> e Source #

class Unvariant' v e | v -> e where Source #

Similar to unvariant, except type variables in v will be made equal to e if possible. That allows the type of Nothing to be inferred as Maybe Char.

>>> unvariant' $ x .=. Nothing .*. mkVariant1 y 'y'
'y'

However, this difference leads to more local error messages (Couldn't match type ‘()’ with ‘Char’), rather than the following with unvariant:

Fail
   '("Variant",
     '[Tagged "left" Char, Tagged "right" ()],
     "must have all values equal to ",
     e))

Methods

unvariant' :: Variant v -> e Source #

Instances

Instances details
(HAllEqVal' (Tagged () e ': v), Unvariant v e) => Unvariant' v e Source # 
Instance details

Defined in Data.HList.Variant

Methods

unvariant' :: Variant v -> e Source #

newtype HMapV f Source #

Apply a function to all possible elements of the variant

Constructors

HMapV f 

Instances

Instances details
(vx ~ Variant x, vy ~ Variant y, HMapAux Variant (HFmap f) x y, SameLength x y) => ApplyAB (HMapV f) vx vy Source #

apply a function to all values that could be in the variant.

Instance details

Defined in Data.HList.Variant

Methods

applyAB :: HMapV f -> vx -> vy Source #

class (SameLength s t, SameLabels s t) => HPrism x s t a b | x s -> a, x t -> b, x s b -> t, x t a -> s where Source #

Make a Prism (Variant s) (Variant t) a b out of a Label.

See Data.HList.Labelable.hLens' is a more overloaded version.

Few type annotations are necessary because of the restriction that s and t have the same labels in the same order, and to get "t" the "a" in "s" is replaced with "b".

Methods

hPrism :: (Choice p, Applicative f) => Label x -> p a (f b) -> p (Variant s) (f (Variant t)) Source #

Instances

Instances details
(MkVariant x b t, HasField x (Variant s) (Maybe a), SameLength s t, SameLabels s t, H2ProjectByLabels '[Label x] s si so, H2ProjectByLabels '[Label x] t ti to, so ~ to, HUpdateAtLabel Variant x b s t, HUpdateAtLabel Variant x a t s) => HPrism (x :: k) s t a b Source # 
Instance details

Defined in Data.HList.Variant

Methods

hPrism :: (Choice p, Applicative f) => Label x -> p a (f b) -> p (Variant s) (f (Variant t)) Source #

mkVariant Source #

Arguments

:: MkVariant x v vs 
=> Label x

the tag

-> v

value to be stored

-> proxy vs

a helper to fix the ordering and types of the potential values that this variant contains. Typically this will be a Proxy, Record or another Variant

-> Variant vs 

data Variant (vs :: [*]) Source #

Variant vs has an implementation similar to Dynamic, except the contained value is one of the elements of the vs list, rather than being one particular instance of Typeable.

>>> v .!. _right
Nothing
>>> v .!. _left
Just 'x'

In some cases the pun quasiquote works with variants,

>>> let f [pun| left right |] = (left,right)
>>> f v
(Just 'x',Nothing)
>>> f w
(Nothing,Just 5)
>>> let add1 v = hMapV (Fun succ :: Fun '[Enum] '()) v
>>> f (add1 v)
(Just 'y',Nothing)
>>> f (add1 w)
(Nothing,Just 6)

Instances

Instances details
Relabeled Variant Source # 
Instance details

Defined in Data.HList.Variant

Methods

relabeled :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (HMapTaggedFn (RecordValuesR s) a, HMapTaggedFn (RecordValuesR b) t, SameLengths '[s, a, t, b], RecordValuesR t ~ RecordValuesR b, RecordValuesR s ~ RecordValuesR a, RecordValues b, RecordValues s, Profunctor p, Functor f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

TypeIndexed Variant TIC Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIC (TagR a)) (f (TIC (TagR b))) -> p (Variant s) (f (Variant t)) Source #

(ExtendsVariant b t, ProjectVariant s a, ProjectExtendVariant s t, HLeftUnion b s bs, HRLabelSet bs, HRearrange (LabelsOf t) bs t) => Projected Variant s t a b Source #
Prism (Variant s) (Variant t) (Variant a) (Variant b)
Instance details

Defined in Data.HList.Labelable

Methods

projected :: forall (ty :: LabeledOpticType) p f. (ty ~ LabelableTy Variant, LabeledOpticP ty p, LabeledOpticF ty f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

HUpdateVariantAtLabelCxt l e v v' n _e => HUpdateAtLabel Variant (l :: k) e v v' Source #
hUpdateAtLabel x e' (mkVariant x e proxy) == mkVariant x e' proxy
hUpdateAtLabel y e' (mkVariant x e proxy) == mkVariant x e  proxy
Instance details

Defined in Data.HList.Variant

Methods

hUpdateAtLabel :: Label l -> e -> Variant v -> Variant v' Source #

(HPrism x s t a b, to ~ (->)) => Labelable (x :: k) Variant s t a b Source #

make a Prism (Variant s) (Variant t) a b

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy Variant :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x Variant s t a b Source #

(HasField x (Record vs) a, HFindLabel x vs n, HNat2Integral n) => HasField (x :: k) (Variant vs) (Maybe a) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hLookupByLabel :: Label x -> Variant vs -> Maybe a Source #

(ApplyAB f te te', HMapCxt Variant f (l ': ls) (l' ': ls')) => HMapAux Variant f (te ': (l ': ls)) (te' ': (l' ': ls')) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hMapAux :: f -> Variant (te ': (l ': ls)) -> Variant (te' ': (l' ': ls')) Source #

ApplyAB f te te' => HMapAux Variant f '[te] '[te'] Source # 
Instance details

Defined in Data.HList.Variant

Methods

hMapAux :: f -> Variant '[te] -> Variant '[te'] Source #

(le ~ Tagged l (Maybe e), HOccursNot (Label l) (LabelsOf v)) => HExtend le (Variant v) Source #

Extension for Variants prefers the first value

(l .=. Nothing) .*. v = v
(l .=. Just e)  .*. _ = mkVariant l e Proxy
Instance details

Defined in Data.HList.Variant

Associated Types

type HExtendR le (Variant v) Source #

Methods

(.*.) :: le -> Variant v -> HExtendR le (Variant v) Source #

(HasField l (Variant r) (Maybe u), HasFieldPath 'True ls u (Maybe v)) => HasFieldPath needJust (Label l ': ls) (Variant r) (Maybe v) Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Variant r -> Maybe v Source #

(HUnzip Variant (x2 ': xs) (y2 ': ys) (xy2 ': xys), SameLength xs ys, SameLength ys xys, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant (tx ': (x2 ': xs)) (ty ': (y2 ': ys)) (txy ': (xy2 ': xys)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

hUnzip :: Variant (txy ': (xy2 ': xys)) -> (Variant (tx ': (x2 ': xs)), Variant (ty ': (y2 ': ys))) Source #

(Unvariant '[txy] txy, tx ~ Tagged t x, ty ~ Tagged t y, txy ~ Tagged t (x, y)) => HUnzip Variant '[tx] '[ty] '[txy] Source # 
Instance details

Defined in Data.HList.Variant

Methods

hUnzip :: Variant '[txy] -> (Variant '[tx], Variant '[ty]) Source #

(Typeable (Variant v), GfoldlVariant v v, GunfoldVariant v v, VariantConstrs v) => Data (Variant v) Source # 
Instance details

Defined in Data.HList.Variant

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Variant v -> c (Variant v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Variant v) #

toConstr :: Variant v -> Constr #

dataTypeOf :: Variant v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Variant v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Variant v)) #

gmapT :: (forall b. Data b => b -> b) -> Variant v -> Variant v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Variant v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Variant v -> r #

gmapQ :: (forall d. Data d => d -> u) -> Variant v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Variant v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Variant v -> m (Variant v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant v -> m (Variant v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant v -> m (Variant v) #

(Monoid x, Monoid (Variant (a ': b))) => Monoid (Variant (Tagged t x ': (a ': b))) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant (Tagged t x ': (a ': b)) #

mappend :: Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

mconcat :: [Variant (Tagged t x ': (a ': b))] -> Variant (Tagged t x ': (a ': b)) #

(Unvariant '[Tagged t x] x, Monoid x) => Monoid (Variant '[Tagged t x]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

mempty :: Variant '[Tagged t x] #

mappend :: Variant '[Tagged t x] -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

mconcat :: [Variant '[Tagged t x]] -> Variant '[Tagged t x] #

(Semigroup x, Semigroup (Variant (a ': b))) => Semigroup (Variant (Tagged t x ': (a ': b))) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(<>) :: Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

sconcat :: NonEmpty (Variant (Tagged t x ': (a ': b))) -> Variant (Tagged t x ': (a ': b)) #

stimes :: Integral b0 => b0 -> Variant (Tagged t x ': (a ': b)) -> Variant (Tagged t x ': (a ': b)) #

(Unvariant '[Tagged t x] x, Semigroup x) => Semigroup (Variant '[Tagged t x]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(<>) :: Variant '[Tagged t x] -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

sconcat :: NonEmpty (Variant '[Tagged t x]) -> Variant '[Tagged t x] #

stimes :: Integral b => b -> Variant '[Tagged t x] -> Variant '[Tagged t x] #

(Bounded x, Bounded z, HRevAppR (Tagged s x ': xs) ('[] :: [Type]) ~ (Tagged t z ': sx), MkVariant t z (Tagged s x ': xs)) => Bounded (Variant (Tagged s x ': xs)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

minBound :: Variant (Tagged s x ': xs) #

maxBound :: Variant (Tagged s x ': xs) #

(Enum x, Bounded x, Enum (Variant (y ': z))) => Enum (Variant (Tagged s x ': (y ': z))) Source #
>>> let t = minBound :: Variant '[Tagged "x" Bool, Tagged "y" Bool]
>>> [t .. maxBound]
[V{x=False},V{x=True},V{y=False},V{y=True}]
Odd behavior
There are some arguments that this instance should not exist.

The last type in the Variant does not need to be Bounded. This means that enumFrom behaves a bit unexpectedly:

>>> [False .. ]
[False,True]
>>> [t .. ]
[V{x=False},V{x=True},V{y=False},V{y=True},V{y=*** Exception: Prelude.Enum.Bool.toEnum: bad argument

This is a "feature" because it allows an Enum (Variant '[Tagged "a" Bool, Tagged "n" Integer])

Another difficult choice is that the lower bound is fromEnum 0 rather than minBound:

>>> take 5 [ minBound :: Variant '[Tagged "b" Bool, Tagged "i" Int] .. ]
[V{b=False},V{b=True},V{i=0},V{i=1},V{i=2}]
Instance details

Defined in Data.HList.Variant

Methods

succ :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) #

pred :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) #

toEnum :: Int -> Variant (Tagged s x ': (y ': z)) #

fromEnum :: Variant (Tagged s x ': (y ': z)) -> Int #

enumFrom :: Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromThen :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromTo :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

enumFromThenTo :: Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> Variant (Tagged s x ': (y ': z)) -> [Variant (Tagged s x ': (y ': z))] #

Enum x => Enum (Variant '[Tagged s x]) Source #

While the instances could be written Enum (Variant '[]) Eq/Ord which cannot produce values, so they have instances for empty variants (unsafeEmptyVariant). Enum can produce values, so it is better that fromEnum 0 :: Variant '[] fails with No instance for Enum (Variant '[]) than producing an invalid variant.

Instance details

Defined in Data.HList.Variant

Methods

succ :: Variant '[Tagged s x] -> Variant '[Tagged s x] #

pred :: Variant '[Tagged s x] -> Variant '[Tagged s x] #

toEnum :: Int -> Variant '[Tagged s x] #

fromEnum :: Variant '[Tagged s x] -> Int #

enumFrom :: Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromThen :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromTo :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

enumFromThenTo :: Variant '[Tagged s x] -> Variant '[Tagged s x] -> Variant '[Tagged s x] -> [Variant '[Tagged s x]] #

ReadVariant v => Read (Variant v) Source #

A corresponding read instance

Instance details

Defined in Data.HList.Variant

ShowVariant vs => Show (Variant vs) Source #

Variants are not opaque

Instance details

Defined in Data.HList.Variant

Methods

showsPrec :: Int -> Variant vs -> ShowS #

show :: Variant vs -> String #

showList :: [Variant vs] -> ShowS #

(Eq (Variant xs), Eq x) => Eq (Variant (x ': xs)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(==) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

(/=) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

Eq (Variant ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.Variant

Methods

(==) :: Variant '[] -> Variant '[] -> Bool #

(/=) :: Variant '[] -> Variant '[] -> Bool #

(Ord x, Ord (Variant xs)) => Ord (Variant (x ': xs)) Source # 
Instance details

Defined in Data.HList.Variant

Methods

compare :: Variant (x ': xs) -> Variant (x ': xs) -> Ordering #

(<) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

(<=) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

(>) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

(>=) :: Variant (x ': xs) -> Variant (x ': xs) -> Bool #

max :: Variant (x ': xs) -> Variant (x ': xs) -> Variant (x ': xs) #

min :: Variant (x ': xs) -> Variant (x ': xs) -> Variant (x ': xs) #

Ord (Variant ('[] :: [Type])) Source # 
Instance details

Defined in Data.HList.Variant

Methods

compare :: Variant '[] -> Variant '[] -> Ordering #

(<) :: Variant '[] -> Variant '[] -> Bool #

(<=) :: Variant '[] -> Variant '[] -> Bool #

(>) :: Variant '[] -> Variant '[] -> Bool #

(>=) :: Variant '[] -> Variant '[] -> Bool #

max :: Variant '[] -> Variant '[] -> Variant '[] #

min :: Variant '[] -> Variant '[] -> Variant '[] #

(SameLength s a, ExtendsVariant s a, SameLength b t, ExtendsVariant b t) => Rearranged Variant (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]) Source # 
Instance details

Defined in Data.HList.Variant

Methods

rearranged :: (Profunctor p, Functor f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

type LabelableTy Variant Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR le (Variant v) Source # 
Instance details

Defined in Data.HList.Variant

type HExtendR le (Variant v) = Variant (UnMaybe le ': v)

castVariant :: (RecordValuesR v ~ RecordValuesR v', SameLength v v') => Variant v -> Variant v' Source #

in ghc>=7.8, coerce is probably a better choice

mkVariant1 :: forall {k} {l :: k} {e}. Label l -> e -> Variant '[Tagged l e] Source #

splitVariant1 :: Variant (Tagged s x ': xs) -> Either x (Variant xs) Source #

splitVariant1' :: Variant (x ': xs) -> Either x (Variant xs) Source #

x ~ Tagged s t

hMapV :: forall {f} {x :: [Type]} {y :: [Type]}. (HMapAux Variant (HFmap f) x y, SameLength' x y, SameLength' y x) => f -> Variant x -> Variant y Source #

shortcut for applyAB . HMapV. hMap is more general

hMapOutV :: forall x y z f. (SameLength x y, HMapAux Variant (HFmap f) x y, Unvariant y z, HMapOutV_gety x z ~ y) => f -> Variant x -> z Source #

hMapOutV f = unvariant . hMapV f, except an ambiguous type variable is resolved by HMapOutV_gety

unvarianted :: (Unvariant' s a, Unvariant' t b, SameLabels s t, SameLength s t, Functor f) => (a -> f b) -> Variant s -> f (Variant t) Source #

Lens (Variant s) (Variant t) a b

Analogue of Control.Lens.chosen :: Lens (Either a a) (Either b b) a b

unvarianted' :: forall {b :: Bool} {t :: [Type]} {a} {f}. (Unvariant1 b t a, HAllEqVal' (Tagged () a ': t), HAllEqVal t b, HAllEqVal (Tagged () a ': t) b, SameLabels t t, SameLength' t t, Functor f) => (a -> f a) -> Variant t -> f (Variant t) Source #

Lens' (Variant s) a

where we might have s ~ '[Tagged t1 a, Tagged t2 a]

zipVR :: (SameLabels fs v, SameLength fs v, ZipVR fs v v', ZipVRCxt fs v v') => Record fs -> Variant v -> Variant v' Source #

>>> let xy = x .*. y .*. emptyProxy
>>> let p = Proxy `asLabelsOf` xy
>>> let vs = [ mkVariant x 1.0 p, mkVariant y () p ]
>>> zipVR (hBuild (+1) id) `map` vs
[V{x=2.0},V{y=()}]

hMaybied :: forall {p} {f} {x :: [Type]} {v1 :: [Type]} {v2 :: [Type]} {r :: [Type]}. (Choice p, Applicative f, HFoldr HMaybiedToVariantFs [Variant ('[] :: [Type])] x [Variant v1], VariantToHMaybied v2 r, VariantToHMaybied v1 x, SameLength' x r, SameLength' r x, HMapAux HList (HFmap HCastF) x r) => p (Variant v1) (f (Variant v2)) -> p (Record x) (f (Record r)) Source #

Prism (Record tma) (Record tmb) (Variant ta) (Variant tb)

see hMaybied'

hMaybied' :: forall {p} {f} {x :: [Type]} {v :: [Type]}. (Choice p, Applicative f, HFoldr HMaybiedToVariantFs [Variant ('[] :: [Type])] x [Variant v], VariantToHMaybied v x, SameLength' x x, HMapAux HList (HFmap HCastF) x x) => p (Variant v) (f (Variant v)) -> p (Record x) (f (Record x)) Source #

Prism' (Record tma) (Variant ta)

where tma and tmb are lists like

tma ~ '[Tagged x (Maybe a), Tagged y (Maybe b)]
ta  ~ '[Tagged x        a , Tagged y        b ]

If one element of the record is Just, the Variant will contain that element. Otherwise, the prism fails.

Note

The types work out to define a prism:

l = prism' variantToHMaybied (listToMaybe . hMaybiedToVariants)

but the law: s^?l ≡ Just a ==> l # a ≡ s is not followed, because we could have:

  s, s2 :: Record '[Tagged "x" (Maybe Int), Tagged "y" (Maybe Char)]
  s = hBuild (Just 1) (Just '2')
  s2 = hBuild (Just 1) Nothing

  v :: Variant '[Tagged "x" Int, Tagged "y" Char]
  v = mkVariant (Label :: Label "x") 1 Proxy

So that s^?l == Just v. But l#v == s2 /= s, while the law requires l#v == s. hMaybied avoids this problem by only producing a value when there is only one present.

hMaybiedToVariants :: (HFoldr HMaybiedToVariantFs [Variant '[]] r [Variant v], VariantToHMaybied v r) => Record r -> [Variant v] Source #

Every element of the record that is Just becomes one element in the resulting list. See hMaybied' example types that r and v can take.

class HDeleteManyCase (b :: Bool) e1 e l l1 | b e1 e l -> l1 where Source #

Methods

hDeleteManyCase :: Proxy b -> Proxy e1 -> e -> HList l -> HList l1 Source #

Instances

Instances details
HDeleteMany e (HList l) (HList l1) => HDeleteManyCase 'True (e :: Type) e l l1 Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteManyCase :: Proxy 'True -> Proxy e -> e -> HList l -> HList l1 Source #

HDeleteMany e1 (HList l) (HList l1) => HDeleteManyCase 'False (e1 :: k) e l (e ': l1) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

Methods

hDeleteManyCase :: Proxy 'False -> Proxy e1 -> e -> HList l -> HList (e ': l1) Source #

class HType2HNatCase (b :: Bool) (e :: *) (l :: [*]) (n :: HNat) | b e l -> n Source #

Helper class

Instances

Instances details
HOccursNot e l => HType2HNatCase 'True e l 'HZero Source # 
Instance details

Defined in Data.HList.HTypeIndexed

HType2HNat e l n => HType2HNatCase 'False e l ('HSucc n) Source # 
Instance details

Defined in Data.HList.HTypeIndexed

hType2HNat :: HType2HNat e l n => proxy1 e -> proxy l -> Proxy n Source #

hTypes2HNats :: HTypes2HNats es l ns => Proxy (es :: [*]) -> hlist l -> Proxy (ns :: [HNat]) Source #

hDeleteAt :: forall {n :: HNat} {l :: [Type]} {e} {proxy1}. (HDeleteAtHNat n l, HType2HNat e l n) => proxy1 e -> HList l -> HList (HDeleteAtHNatR n l) Source #

hUpdateAt :: forall {n :: HNat} {e} {l :: [Type]}. (HUpdateAtHNat' n e l l, HType2HNat e l n) => e -> HList l -> HList (HUpdateAtHNatR n e l) Source #

hProjectBy :: forall {k} {ns :: [HNat]} {hlist} {l :: k} {z :: [Type]} {es :: [Type]}. (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (hlist l, Proxy 'HZero)) z, Apply (FHUProj 'True ns) (hlist l, Proxy 'HZero), HTypes2HNats es l ns) => Proxy es -> hlist l -> HList z Source #

hSplitBy :: forall {k} {ns :: [HNat]} {hlist} {l :: k} {z1 :: [Type]} {z2 :: [Type]} {es :: [Type]}. (HUnfoldFD (FHUProj 'True ns) (ApplyR (FHUProj 'True ns) (hlist l, Proxy 'HZero)) z1, HUnfoldFD (FHUProj 'False ns) (ApplyR (FHUProj 'False ns) (hlist l, Proxy 'HZero)) z2, Apply (FHUProj 'True ns) (hlist l, Proxy 'HZero), Apply (FHUProj 'False ns) (hlist l, Proxy 'HZero), HTypes2HNats es l ns) => Proxy es -> hlist l -> (HList z1, HList z2) Source #

class Monad m => TransTIPM m op db where Source #

In March 2010, Andrew Frank extended the problem for monadic operations. This is the monadic version of TIPTransform.hs in the present directory.

This is the TF implementation. When specifying the operation to perform over a TIP, we can leave it polymorphic over the monad. The type checker will instantiate the monad based on the context.

Methods

ttipM :: op -> TIP db -> m (TIP db) Source #

Instances

Instances details
(Monad m, HMember (Tagged op op) db b, Arity (m' op) n, TransTIPM1 b n m (m' op) db) => TransTIPM m (m' op) db Source # 
Instance details

Defined in Data.HList.TIP

Methods

ttipM :: m' op -> TIP db -> m (TIP db) Source #

class TransTIP op db where Source #

Transforming a TIP: applying to a TIP a (polyvariadic) function that takes arguments from a TIP and updates the TIP with the result.

In more detail: we have a typed-indexed collection TIP and we would like to apply a transformation function to it, whose argument types and the result type are all in the TIP. The function should locate its arguments based on their types, and update the TIP with the result. The function may have any number of arguments, including zero; the order of arguments should not matter.

The problem was posed by Andrew U. Frank on Haskell-Cafe, Sep 10, 2009. http://www.haskell.org/pipermail/haskell-cafe/2009-September/066217.html The problem is an interesting variation of the keyword argument problem.

Examples can be found in examples/TIPTransform.hs and examples/TIPTransformM.hs

Methods

ttip :: op -> TIP db -> TIP db Source #

Instances

Instances details
(HMember (Tagged op op) db b, Arity op n, TransTIP1 b n op db) => TransTIP op db Source # 
Instance details

Defined in Data.HList.TIP

Methods

ttip :: op -> TIP db -> TIP db Source #

type family TagR (a :: [*]) :: [*] Source #

Instances

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

Defined in Data.HList.TIP

type TagR ('[] :: [Type]) = '[] :: [Type]
type TagR (x ': xs) Source # 
Instance details

Defined in Data.HList.TIP

type TagR (x ': xs) = Tagged x x ': TagR xs

type TagUntag xs = TagUntagFD xs (TagR xs) Source #

class SameLength a ta => TagUntagFD a ta | a -> ta, ta -> a where Source #

TagR can also be used to avoid redundancy when defining types for TIC and TIP.

 type XShort = TagR [A,B,C,D]
 type XLong = [Tagged A A, Tagged B B, Tagged C C, Tagged D D]

an equivalent FD version, which is slightly better with respect to simplifying types containing type variables (in ghc-7.8 and 7.6): http://stackoverflow.com/questions/24110410/

With ghc-7.10 (http://ghc.haskell.org/trac/ghc/ticket/10009) the FD version is superior to the TF version:

class (UntagR (TagR a) ~ a) => TagUntag a where
    type TagR a :: [*]
    hTagSelf :: HList a -> HList (TagR a)
    hUntagSelf :: HList (TagR a) -> HList a

instance TagUntag '[] where
    type TagR '[] = '[]
    hTagSelf _ = HNil
    hUntagSelf _ = HNil

instance TagUntag xs => TagUntag (x ': xs) where
    type TagR (x ': xs) = Tagged x x ': TagR xs
    hTagSelf (HCons x xs) = Tagged x HCons hTagSelf xs
    hUntagSelf (HCons (Tagged x) xs) = x HCons hUntagSelf xs

type family UntagR (xs :: [*]) :: [*]
type instance UntagR '[] = '[]
type instance UntagR (x ': xs) = Untag1 x ': UntagR xs

Length information should flow backwards

>>> let len2 x = x `asTypeOf` (undefined :: HList '[a,b])
>>> let f = len2 $ hTagSelf (hReplicate Proxy ())
>>> :t f
f :: HList '[Tagged () (), Tagged () ()]

Methods

hTagSelf :: HList a -> HList ta Source #

hUntagSelf :: HList ta -> HList a Source #

Instances

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

Defined in Data.HList.TIP

Methods

hTagSelf :: HList '[] -> HList '[] Source #

hUntagSelf :: HList '[] -> HList '[] Source #

(TagUntagFD xs ys, txx ~ Tagged x x) => TagUntagFD (x ': xs) (txx ': ys) Source # 
Instance details

Defined in Data.HList.TIP

Methods

hTagSelf :: HList (x ': xs) -> HList (txx ': ys) Source #

hUntagSelf :: HList (txx ': ys) -> HList (x ': xs) Source #

class HAllTaggedEq (l :: [*]) Source #

Instances

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

Defined in Data.HList.TIP

(HAllTaggedEq l, tee ~ Tagged e e') => HAllTaggedEq (tee ': l) Source # 
Instance details

Defined in Data.HList.TIP

data TIP (l :: [*]) Source #

TIPs are like Record, except element "i" of the list "l" has type Tagged e_i e_i

Instances

Instances details
TypeIndexed Record TIP Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIP (TagR a)) (f (TIP (TagR b))) -> p (Record s) (f (Record t)) Source #

(HZipList xL yL xyL, lty ~ (HList xyL -> (HList xL, HList yL)), Coercible lty (TIP xy -> (TIP x, TIP y)), UntagR x ~ xL, TagR xL ~ x, UntagR y ~ yL, TagR yL ~ y, UntagR xy ~ xyL, TagR xyL ~ xy, SameLengths '[x, y, xy], UntagTag x, UntagTag y, UntagTag xy) => HUnzip TIP x y xy Source # 
Instance details

Defined in Data.HList.TIP

Methods

hUnzip :: TIP xy -> (TIP x, TIP y) Source #

(HUnzip TIP x y xy, HZipList xL yL xyL, lty ~ (HList xL -> HList yL -> HList xyL), Coercible lty (TIP x -> TIP y -> TIP xy), UntagR x ~ xL, UntagR y ~ yL, UntagR xy ~ xyL, UntagTag x, UntagTag y, UntagTag xy) => HZip TIP x y xy Source # 
Instance details

Defined in Data.HList.TIP

Methods

hZip :: TIP x -> TIP y -> TIP xy Source #

(HDeleteAtLabel Record e v v', HTypeIndexed v') => HDeleteAtLabel TIP (e :: k) v v' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hDeleteAtLabel :: Label e -> TIP v -> TIP v' Source #

(HUpdateAtLabel Record e' e r r', HTypeIndexed r', e ~ e') => HUpdateAtLabel TIP (e' :: Type) e r r' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hUpdateAtLabel :: Label e' -> e -> TIP r -> TIP r' Source #

LabelableTIPCxt x s t a b => Labelable (x :: k) TIP s t a b Source #

make a Lens' (TIP s) a.

tipyLens provides a Lens (TIP s) (TIP t) a b, which tends to need too many type annotations to be practical

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy TIP :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x TIP s t a b Source #

(e ~ e', HasField e (Record l) e') => HasField (e :: Type) (TIP l) e' Source # 
Instance details

Defined in Data.HList.TIP

Methods

hLookupByLabel :: Label e -> TIP l -> e' Source #

SubType (TIP l :: Type) (TIP ('[] :: [Type])) Source #

Subtyping for TIPs

Instance details

Defined in Data.HList.TIP

(HOccurs e (TIP l1), SubType (TIP l1) (TIP l2)) => SubType (TIP l1 :: Type) (TIP (e ': l2) :: Type) Source # 
Instance details

Defined in Data.HList.TIP

(HRLabelSet (Tagged e e ': l), HTypeIndexed l) => HExtend e (TIP l) Source # 
Instance details

Defined in Data.HList.TIP

Associated Types

type HExtendR e (TIP l) Source #

Methods

(.*.) :: e -> TIP l -> HExtendR e (TIP l) Source #

tee ~ Tagged e e => HOccurs e (TIP '[tee]) Source #

One occurrence and nothing is left

This variation provides an extra feature for singleton lists. That is, the result type is unified with the element in the list. Hence the explicit provision of a result type can be omitted.

Instance details

Defined in Data.HList.TIP

Methods

hOccurs :: TIP '[tee] -> e Source #

HasField e (Record (x ': (y ': l))) e => HOccurs e (TIP (x ': (y ': l))) Source # 
Instance details

Defined in Data.HList.TIP

Methods

hOccurs :: TIP (x ': (y ': l)) -> e Source #

(TypeablePolyK xs, Typeable (HList xs), Data (HList xs)) => Data (TIP xs) Source # 
Instance details

Defined in Data.HList.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TIP xs -> c (TIP xs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TIP xs) #

toConstr :: TIP xs -> Constr #

dataTypeOf :: TIP xs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TIP xs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TIP xs)) #

gmapT :: (forall b. Data b => b -> b) -> TIP xs -> TIP xs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TIP xs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TIP xs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TIP xs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TIP xs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TIP xs -> m (TIP xs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TIP xs -> m (TIP xs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TIP xs -> m (TIP xs) #

Monoid (HList a) => Monoid (TIP a) Source # 
Instance details

Defined in Data.HList.TIP

Methods

mempty :: TIP a #

mappend :: TIP a -> TIP a -> TIP a #

mconcat :: [TIP a] -> TIP a #

Semigroup (HList a) => Semigroup (TIP a) Source # 
Instance details

Defined in Data.HList.TIP

Methods

(<>) :: TIP a -> TIP a -> TIP a #

sconcat :: NonEmpty (TIP a) -> TIP a #

stimes :: Integral b => b -> TIP a -> TIP a #

Bounded (HList r) => Bounded (TIP r) Source # 
Instance details

Defined in Data.HList.TIP

Methods

minBound :: TIP r #

maxBound :: TIP r #

Ix (HList r) => Ix (TIP r) Source # 
Instance details

Defined in Data.HList.TIP

Methods

range :: (TIP r, TIP r) -> [TIP r] #

index :: (TIP r, TIP r) -> TIP r -> Int #

unsafeIndex :: (TIP r, TIP r) -> TIP r -> Int #

inRange :: (TIP r, TIP r) -> TIP r -> Bool #

rangeSize :: (TIP r, TIP r) -> Int #

unsafeRangeSize :: (TIP r, TIP r) -> Int #

HMapOut (HComp HShow HUntag) l String => Show (TIP l) Source # 
Instance details

Defined in Data.HList.TIP

Methods

showsPrec :: Int -> TIP l -> ShowS #

show :: TIP l -> String #

showList :: [TIP l] -> ShowS #

Eq (HList a) => Eq (TIP a) Source # 
Instance details

Defined in Data.HList.TIP

Methods

(==) :: TIP a -> TIP a -> Bool #

(/=) :: TIP a -> TIP a -> Bool #

Ord (HList r) => Ord (TIP r) Source # 
Instance details

Defined in Data.HList.TIP

Methods

compare :: TIP r -> TIP r -> Ordering #

(<) :: TIP r -> TIP r -> Bool #

(<=) :: TIP r -> TIP r -> Bool #

(>) :: TIP r -> TIP r -> Bool #

(>=) :: TIP r -> TIP r -> Bool #

max :: TIP r -> TIP r -> TIP r #

min :: TIP r -> TIP r -> TIP r #

(HAppend (HList l) (HList l'), HTypeIndexed (HAppendListR l l')) => HAppend (TIP l) (TIP l') Source # 
Instance details

Defined in Data.HList.TIP

Methods

hAppend :: TIP l -> TIP l' -> HAppendR (TIP l) (TIP l') Source #

type LabelableTy TIP Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR e (TIP l) Source # 
Instance details

Defined in Data.HList.TIP

type HExtendR e (TIP l) = TIP (Tagged e e ': l)
type HAppendR (TIP l :: Type) (TIP l' :: Type) Source # 
Instance details

Defined in Data.HList.TIP

type HAppendR (TIP l :: Type) (TIP l' :: Type) = TIP (HAppendListR l l')

tipyUpdate :: forall {record} {v} {r :: [Type]}. (HUpdateAtLabel record v v r r, SameLength' r r) => v -> record r -> record r Source #

tipyProject :: forall {l :: [Type]} {ls :: [Type]} {r :: [Type]} {b :: [Type]} {proxy}. (HAllTaggedEq l, HLabelSet (LabelsOf l), HAllTaggedLV l, H2ProjectByLabels ls r l b) => proxy ls -> TIP r -> TIP l Source #

Use Labels to specify the first argument

tipyLens' :: forall {a} {t :: [Type]} {f}. (HasField a (Record t) a, HUpdateAtLabel2 a a t t, HAllTaggedEq t, HLabelSet (LabelsOf t), HAllTaggedLV t, SameLength' t t, SameLabels t t, Functor f) => (a -> f a) -> TIP t -> f (TIP t) Source #

provides a Lens' (TIP s) a. hLens' :: Label a -> Lens' (TIP s) a is another option.

tipyLens :: forall {n :: HNat} {x} {xs1 :: [Type]} {l1 :: [Type]} {a1} {xs2 :: [Type]} {b :: Bool} {a2} {f}. (HSplitAt1 ('[] :: [Type]) n (Tagged x x ': xs1) l1 (Tagged a1 a1 ': xs2), HAppendList1 l1 (Tagged a1 a1 ': xs2) (Tagged x x ': xs1), SameLength' (HReplicateR n ()) l1, HLengthEq1 l1 n, HLengthEq2 l1 n, HEq (Label a1) (Label x) b, HFind2 b (Label a1) (LabelsOf xs1) (Label x ': LabelsOf xs1) n, HAllTaggedEq (HAppendListR l1 (Tagged a2 a2 ': xs2)), HLabelSet (LabelsOf (HAppendListR l1 (Tagged a2 a2 ': xs2))), HAllTaggedLV (HAppendListR l1 (Tagged a2 a2 ': xs2)), HAppendList l1 (Tagged a2 a2 ': xs2), Functor f) => (a1 -> f a2) -> TIP (Tagged x x ': xs1) -> f (TIP (HAppendListR l1 (Tagged a2 a2 ': xs2))) Source #

provides a Lens (TIP s) (TIP t) a b

When using set (also known as .~), tipyLens' can address the ambiguity as to which field "a" should actually be updated.

tipyProject2 :: forall {ls :: [Type]} {r :: [Type]} {l1 :: [Type]} {l2 :: [Type]} {proxy}. (H2ProjectByLabels ls r l1 l2, HAllTaggedEq l1, HAllTaggedEq l2, HLabelSet (LabelsOf l1), HLabelSet (LabelsOf l2), HAllTaggedLV l1, HAllTaggedLV l2) => proxy ls -> TIP r -> (TIP l1, TIP l2) Source #

The same as tipyProject, except also return the types not requested in the proxy argument

tipHList :: forall {p} {f} {a1 :: [Type]} {ta :: [Type]} {a2 :: [Type]} {l :: [Type]}. (Profunctor p, Functor f, TagUntagFD a1 ta, TagUntagFD a2 l) => p (HList a1) (f (HList a2)) -> p (TIP ta) (f (TIP l)) Source #

Iso (TIP (TagR a)) (TIP (TagR b)) (HList a) (HList b)

tipHList' :: forall {p} {f} {a :: [Type]} {l :: [Type]}. (Profunctor p, Functor f, TagUntagFD a l) => p (HList a) (f (HList a)) -> p (TIP l) (f (TIP l)) Source #

Iso' (TIP (TagR s)) (HList a)

tipRecord :: forall {p} {f} {r :: [Type]} {l :: [Type]}. (Profunctor p, Functor f) => p (Record r) (f (Record l)) -> p (TIP r) (f (TIP l)) Source #

Iso (TIP s) (TIP t) (Record s) (Record t)

typeIndexed may be more appropriate

tipRecord' :: forall {p} {f} {l :: [Type]}. (Profunctor p, Functor f) => p (Record l) (f (Record l)) -> p (TIP l) (f (TIP l)) Source #

Iso' (TIP (TagR s)) (Record a)

ticPrism :: (TICPrism s t a b, SameLength s t, Choice p, Applicative f) => (a `p` f b) -> TIC s `p` f (TIC t) Source #

class TypeIndexed r tr | r -> tr, tr -> r where Source #

Conversion between type indexed collections (TIC and TIP) and the corresponding collection that has other label types (Variant and Record respectively)

See typeIndexed'

Methods

typeIndexed :: forall p f s t a b. (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (tr (TagR a)) (f (tr (TagR b))) -> p (r s) (f (r t)) Source #

Iso (r s) (r t) (tr a) (tr b)

Instances

Instances details
TypeIndexed Record TIP Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIP (TagR a)) (f (TIP (TagR b))) -> p (Record s) (f (Record t)) Source #

TypeIndexed Variant TIC Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIC (TagR a)) (f (TIC (TagR b))) -> p (Variant s) (f (Variant t)) Source #

data TIC (l :: [*]) Source #

A datatype for type-indexed co-products. A TIC is just a Variant, where the elements of the type-level list "l" are in the form Tagged x x.

Instances

Instances details
TypeIndexed Variant TIC Source # 
Instance details

Defined in Data.HList.TIC

Methods

typeIndexed :: forall p f (s :: [Type]) (t :: [Type]) (a :: [Type]) (b :: [Type]). (TypeIndexedCxt s t a b, Profunctor p, Functor f) => p (TIC (TagR a)) (f (TIC (TagR b))) -> p (Variant s) (f (Variant t)) Source #

HMapAux Variant f xs ys => HMapAux TIC f xs ys Source # 
Instance details

Defined in Data.HList.TIC

Methods

hMapAux :: f -> TIC xs -> TIC ys Source #

(TICPrism s t a b, Label x ~ Label a, a ~ b, s ~ t, SameLength s t) => Labelable (x :: k) TIC s t a b Source #
hLens' :: Label a -> Prism' (TIC s) a

note that a more general function ticPrism :: Prism (TIC s) (TIC t) a b, cannot have an instance of Labelable

Note: `x :: k` according to the instance head, but the instance body forces the kind variable to be * later on. IE. (k ~ *)

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy TIC :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x TIC s t a b Source #

HasField o (Variant l) (Maybe o) => HasField (o :: Type) (TIC l) (Maybe o) Source #

Public destructor (or, open union's projection function)

Instance details

Defined in Data.HList.TIC

Methods

hLookupByLabel :: Label o -> TIC l -> Maybe o Source #

(me ~ Maybe e, HOccursNot (Tagged e e) l) => HExtend me (TIC l) Source #
Nothing .*. x = x
Just a .*. y = mkTIC a
Instance details

Defined in Data.HList.TIC

Associated Types

type HExtendR me (TIC l) Source #

Methods

(.*.) :: me -> TIC l -> HExtendR me (TIC l) Source #

(HasField o (TIC l) mo, mo ~ Maybe o) => HOccurs mo (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

hOccurs :: TIC l -> mo Source #

(TypeablePolyK xs, Typeable (Variant xs), Data (Variant xs)) => Data (TIC xs) Source # 
Instance details

Defined in Data.HList.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TIC xs -> c (TIC xs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TIC xs) #

toConstr :: TIC xs -> Constr #

dataTypeOf :: TIC xs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TIC xs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TIC xs)) #

gmapT :: (forall b. Data b => b -> b) -> TIC xs -> TIC xs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TIC xs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TIC xs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TIC xs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TIC xs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TIC xs -> m (TIC xs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TIC xs -> m (TIC xs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TIC xs -> m (TIC xs) #

Monoid (Variant l) => Monoid (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

mempty :: TIC l #

mappend :: TIC l -> TIC l -> TIC l #

mconcat :: [TIC l] -> TIC l #

Semigroup (Variant l) => Semigroup (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

(<>) :: TIC l -> TIC l -> TIC l #

sconcat :: NonEmpty (TIC l) -> TIC l #

stimes :: Integral b => b -> TIC l -> TIC l #

Bounded (Variant l) => Bounded (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

minBound :: TIC l #

maxBound :: TIC l #

Enum (Variant l) => Enum (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

succ :: TIC l -> TIC l #

pred :: TIC l -> TIC l #

toEnum :: Int -> TIC l #

fromEnum :: TIC l -> Int #

enumFrom :: TIC l -> [TIC l] #

enumFromThen :: TIC l -> TIC l -> [TIC l] #

enumFromTo :: TIC l -> TIC l -> [TIC l] #

enumFromThenTo :: TIC l -> TIC l -> TIC l -> [TIC l] #

Ix (Variant l) => Ix (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

range :: (TIC l, TIC l) -> [TIC l] #

index :: (TIC l, TIC l) -> TIC l -> Int #

unsafeIndex :: (TIC l, TIC l) -> TIC l -> Int #

inRange :: (TIC l, TIC l) -> TIC l -> Bool #

rangeSize :: (TIC l, TIC l) -> Int #

unsafeRangeSize :: (TIC l, TIC l) -> Int #

(ReadVariant l, HAllTaggedEq l, HRLabelSet l) => Read (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

ShowVariant l => Show (TIC l) Source #

TICs are not opaque

Instance details

Defined in Data.HList.TIC

Methods

showsPrec :: Int -> TIC l -> ShowS #

show :: TIC l -> String #

showList :: [TIC l] -> ShowS #

Eq (Variant l) => Eq (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

(==) :: TIC l -> TIC l -> Bool #

(/=) :: TIC l -> TIC l -> Bool #

Ord (Variant l) => Ord (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

Methods

compare :: TIC l -> TIC l -> Ordering #

(<) :: TIC l -> TIC l -> Bool #

(<=) :: TIC l -> TIC l -> Bool #

(>) :: TIC l -> TIC l -> Bool #

(>=) :: TIC l -> TIC l -> Bool #

max :: TIC l -> TIC l -> TIC l #

min :: TIC l -> TIC l -> TIC l #

type LabelableTy TIC Source # 
Instance details

Defined in Data.HList.Labelable

type HExtendR me (TIC l) Source # 
Instance details

Defined in Data.HList.TIC

type HExtendR me (TIC l) = TIC (Tagged (UnMaybe me) (UnMaybe me) ': l)

ticVariant :: forall {p} {f} {l1 :: [Type]} {l2 :: [Type]}. (Profunctor p, Functor f) => p (Variant l1) (f (Variant l2)) -> p (TIC l1) (f (TIC l2)) Source #

Iso (TIC s) (TIC t) (Variant s) (Variant t)

typeIndexed may be more appropriate

ticVariant' :: forall {p} {f} {l :: [Type]}. (Profunctor p, Functor f) => p (Variant l) (f (Variant l)) -> p (TIC l) (f (TIC l)) Source #

Iso' (TIC s) (Variant s)

typeIndexed' :: forall {t :: [Type]} {r} {tr} {p} {f}. (Coercible (TagR (RecordValuesR t)) t, TypeIndexed r tr, HMapAux HList TaggedFn (RecordValuesR t) t, RecordValues t, SameLabels t t, HAllTaggedLV t, HLabelSet (LabelsOf t), TagUntagFD (RecordValuesR t) (TagR (RecordValuesR t)), Profunctor p, Functor f, SameLength' t t, SameLength' (RecordValuesR t) (RecordValuesR t)) => p (tr (TagR (RecordValuesR t))) (f (tr (TagR (RecordValuesR t)))) -> p (r t) (f (r t)) Source #

Iso' (Variant s) (TIC a)
Iso' (Record s) (TIP a)

where s has a type like '[Tagged "x" Int], and a has a type like '[Tagged Int Int].

mkTIC' Source #

Arguments

:: forall i l proxy. (HTypeIndexed l, MkVariant i i l) 
=> i 
-> proxy l

the ordering of types in the l :: [*] matters. This argument is intended to fix the ordering it can be a Record, Variant, TIP, Proxy

-> TIC l 

Public constructor (or, open union's injection function)

mkTIC1 :: forall i. MkVariant i i '[Tagged i i] => i -> TIC '[Tagged i i] Source #

make a TIC that contains one element

mkTIC :: forall {i} {l :: [Type]} {n :: HNat}. (HFind1 i (UnLabel i (LabelsOf l)) (UnLabel i (LabelsOf l)) n, HasField i (Record l) i, HAllTaggedLV l, HLabelSet (LabelsOf l), HAllTaggedEq l, KnownNat (HNat2Nat n)) => i -> TIC l Source #

make a TIC for use in contexts where the result type is fixed

ticPrism' :: forall s t a b. (HPrism a s t a b, a ~ b, s ~ t) => forall f p. (Applicative f, Choice p) => (a `p` f b) -> TIC s `p` f (TIC t) Source #

Prism' (TIC s) a

class Projected r s t a b where Source #

Sometimes it may be more convenient to operate on a record/variant that only contains the fields of interest. projected can then be used to apply that function to a record that contains additional elements.

>>> :set -XViewPatterns
>>> import Data.HList.RecordPuns
>>> let f [pun| (x y) |] = case x+y of z -> [pun| z |]
>>> :t f
f :: Num v =>
     Record '[Tagged "x" v, Tagged "y" v] -> Record '[Tagged "z" v]
>>> let r = (let x = 1; y = 2; z = () in [pun| x y z |])
>>> r
Record{x=1,y=2,z=()}
>>> r & sameLabels . projected %~ f
Record{x=1,y=2,z=3}

Methods

projected :: (ty ~ LabelableTy r, LabeledOpticP ty p, LabeledOpticF ty f) => (r a `p` f (r b)) -> r s `p` f (r t) Source #

Instances

Instances details
(H2ProjectByLabels (LabelsOf a) s a_ _s_minus_a, HRLabelSet a_, HRLabelSet a, HRearrange (LabelsOf a) a_ a, HLeftUnion b s bs, HRLabelSet bs, HRearrange (LabelsOf t) bs t, HRLabelSet t) => Projected Record s t a b Source #
Lens rs rt ra rb

where rs ~ Record s, rt ~ Record t, ra ~ Record a, rb ~ Record b

Instance details

Defined in Data.HList.Labelable

Methods

projected :: forall (ty :: LabeledOpticType) p f. (ty ~ LabelableTy Record, LabeledOpticP ty p, LabeledOpticF ty f) => p (Record a) (f (Record b)) -> p (Record s) (f (Record t)) Source #

(ExtendsVariant b t, ProjectVariant s a, ProjectExtendVariant s t, HLeftUnion b s bs, HRLabelSet bs, HRearrange (LabelsOf t) bs t) => Projected Variant s t a b Source #
Prism (Variant s) (Variant t) (Variant a) (Variant b)
Instance details

Defined in Data.HList.Labelable

Methods

projected :: forall (ty :: LabeledOpticType) p f. (ty ~ LabelableTy Variant, LabeledOpticP ty p, LabeledOpticF ty f) => p (Variant a) (f (Variant b)) -> p (Variant s) (f (Variant t)) Source #

toLabel :: EnsureLabel x y => x -> y Source #

class SameLength s t => Labelable (x :: k) (r :: [*] -> *) s t a b | x s -> a, x t -> b, x s b -> t, x t a -> s where Source #

r
is Record, Variant. TIP and TIC also have instances, but generally tipyLens' and ticPrism' are more appropriate.
x
is the label for the field. It tends to have kind Symbol, but others are supported in principle.

Associated Types

type LabelableTy r :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x r s t a b Source #

Instances

Instances details
LabeledCxt1 s t a b => Labelable (x :: k) LabeledR s t a b Source #

used with toLabel and/or .==.

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy LabeledR :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x LabeledR s t a b Source #

HLens x Record s t a b => Labelable (x :: k) Record s t a b Source #

make a Lens (Record s) (Record t) a b

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy Record :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x Record s t a b Source #

(s ~ t, a ~ b, IArray UArray a, a ~ GetElemTy s, HLensCxt x RecordU s t a b) => Labelable (x :: k) RecordU s t a b Source #

make a Lens' (RecordU s) a

Instance details

Defined in Data.HList.RecordU

Associated Types

type LabelableTy RecordU :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x RecordU s t a b Source #

(TICPrism s t a b, Label x ~ Label a, a ~ b, s ~ t, SameLength s t) => Labelable (x :: k) TIC s t a b Source #
hLens' :: Label a -> Prism' (TIC s) a

note that a more general function ticPrism :: Prism (TIC s) (TIC t) a b, cannot have an instance of Labelable

Note: `x :: k` according to the instance head, but the instance body forces the kind variable to be * later on. IE. (k ~ *)

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy TIC :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x TIC s t a b Source #

LabelableTIPCxt x s t a b => Labelable (x :: k) TIP s t a b Source #

make a Lens' (TIP s) a.

tipyLens provides a Lens (TIP s) (TIP t) a b, which tends to need too many type annotations to be practical

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy TIP :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x TIP s t a b Source #

(HPrism x s t a b, to ~ (->)) => Labelable (x :: k) Variant s t a b Source #

make a Prism (Variant s) (Variant t) a b

Instance details

Defined in Data.HList.Labelable

Associated Types

type LabelableTy Variant :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x Variant s t a b Source #

type LabeledOptic (x :: k) (r :: [*] -> *) (s :: [*]) (t :: [*]) (a :: *) (b :: *) = forall ty to p f. (ty ~ LabelableTy r, LabeledOpticF ty f, LabeledOpticP ty p, LabeledOpticTo ty x to) => (a `p` f b) `to` (r s `p` f (r t)) Source #

This alias is the same as Control.Lens.Optic, except the (->) in Optic is a type parameter to in LabeledOptic.

Depending on the collection type (see instances of LabelableTy), the type variables to, p, f are constrained such that the resulting type is a Lens (r s) (r t) a b, Prism (r s) (r t) a b or a LabeledTo x _ _. The latter can be used to recover the label (x) when used as an argument to .==. or equivalently toLabel.

(.==.) :: forall {k} {x} {l :: k} {v}. EnsureLabel x (Label l) => x -> v -> Tagged l v infixr 4 Source #

modification of .=. which works with the labels from this module, and those from Data.HList.Label6. Note that this is not strictly a generalization of .=., since it does not work with labels like Data.HList.Label3 which have the wrong kind.

projected' :: forall {r} {p} {f} {t :: [Type]} {b :: [Type]}. (LabeledOpticP (LabelableTy r) p, LabeledOpticF (LabelableTy r) f, Projected r t t b b) => p (r b) (f (r b)) -> p (r t) (f (r t)) Source #

Lens' (Record s) (Record a)
Prism' (Variant s) (Variant a)

data BoxF Source #

Instances

Instances details
(ux ~ RecordU x, hx ~ HList x, RecordUToRecord x) => ApplyAB BoxF ux hx Source # 
Instance details

Defined in Data.HList.RecordU

Methods

applyAB :: BoxF -> ux -> hx Source #

data UnboxF Source #

Instances

Instances details
(hx ~ HList x, ux ~ RecordU x, RecordToRecordU x) => ApplyAB UnboxF hx ux Source # 
Instance details

Defined in Data.HList.RecordU

Methods

applyAB :: UnboxF -> hx -> ux Source #

class RecordUToRecord x Source #

Minimal complete definition

recordUToRecord

Instances

Instances details
(HMapCxt HList TaggedFn (RecordValuesR x) x, IArray UArray (GetElemTy x), HList2List (RecordValuesR x) (GetElemTy x)) => RecordUToRecord x Source # 
Instance details

Defined in Data.HList.RecordU

class RecordToRecordU x Source #

Minimal complete definition

recordToRecordU

Instances

Instances details
(RecordValues x, HList2List (RecordValuesR x) (GetElemTy x), HNat2Integral n, HLengthEq x n, IArray UArray (GetElemTy x)) => RecordToRecordU x Source # 
Instance details

Defined in Data.HList.RecordU

class HFindMany (ls :: [k]) (r :: [k]) (ns :: [HNat]) | ls r -> ns Source #

behaves like map HFind

Instances

Instances details
HFindMany ('[] :: [k]) (r :: [k]) ('[] :: [HNat]) Source # 
Instance details

Defined in Data.HList.RecordU

(HFind l r n, HFindMany ls r ns) => HFindMany (l ': ls :: [k]) (r :: [k]) (n ': ns) Source # 
Instance details

Defined in Data.HList.RecordU

class HUpdateMany lv rx where Source #

analogous flip //. Similar to .<++., except it is restricted to cases where the left argument holds a subset of elements.

Methods

hUpdateMany :: Record lv -> rx -> rx Source #

Instances

Instances details
(HLeftUnion lv x lvx, HRLabelSet x, HLabelSet (LabelsOf x), HRearrange (LabelsOf x) lvx x) => HUpdateMany lv (Record x) Source #

implementation in terms of .<++.

Instance details

Defined in Data.HList.RecordU

Methods

hUpdateMany :: Record lv -> Record x -> Record x Source #

(RecordValues lv, HList2List (RecordValuesR lv) v, HFindMany (LabelsOf lv) (LabelsOf r) ixs, IArray UArray v, v ~ GetElemTy r, HNats2Integrals ixs) => HUpdateMany lv (RecordU r) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hUpdateMany :: Record lv -> RecordU r -> RecordU r Source #

class ElemTyEq (xs :: [*]) Source #

all elements of the list have the same type

Instances

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

Defined in Data.HList.RecordU

t1v ~ Tagged t v => ElemTyEq (t1v ': rest) Source # 
Instance details

Defined in Data.HList.RecordU

(t1v ~ Tagged t1 v, t2v ~ Tagged t2 v, ElemTyEq (tv2 ': rest)) => ElemTyEq (tv1 ': (tv2 ': rest)) Source # 
Instance details

Defined in Data.HList.RecordU

type family HSubtract (n1 :: HNat) (n2 :: HNat) :: Either HNat HNat Source #

HSubtract a b is Left (a-b), Right (b-a) or Right HZero

Instances

Instances details
type HSubtract 'HZero 'HZero Source # 
Instance details

Defined in Data.HList.RecordU

type HSubtract 'HZero ('HSucc y) Source # 
Instance details

Defined in Data.HList.RecordU

type HSubtract 'HZero ('HSucc y) = 'Right ('HSucc y) :: Either HNat HNat
type HSubtract ('HSucc y) 'HZero Source # 
Instance details

Defined in Data.HList.RecordU

type HSubtract ('HSucc y) 'HZero = 'Left ('HSucc y) :: Either HNat HNat
type HSubtract ('HSucc x) ('HSucc y) Source # 
Instance details

Defined in Data.HList.RecordU

type HSubtract ('HSucc x) ('HSucc y) = HSubtract x y

class HLookupByHNatUS1 (r :: Either HNat HNat) (n :: HNat) (u :: [*]) (us :: [*]) (e :: *) | r n u us -> e Source #

Minimal complete definition

hLookupByHNatUS1

Instances

Instances details
(HNat2Integral n, HLookupByHNatR n u ~ le, le ~ Tagged l e, IArray UArray e, e ~ GetElemTy u) => HLookupByHNatUS1 ('Left t :: Either HNat HNat) n u us le Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByHNatUS1 :: Proxy ('Left t) -> Proxy n -> RecordU u -> HList us -> le Source #

HLookupByHNatUS t us e => HLookupByHNatUS1 ('Right t :: Either HNat HNat) n u us e Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByHNatUS1 :: Proxy ('Right t) -> Proxy n -> RecordU u -> HList us -> e Source #

class HLookupByHNatUS (n :: HNat) (us :: [*]) (e :: *) | n us -> e Source #

Minimal complete definition

hLookupByHNatUS

Instances

Instances details
(r ~ HSubtract (HLength u) n, RecordU u ~ ru, HLookupByHNatUS1 r n u us e) => HLookupByHNatUS n (ru ': us) e Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByHNatUS :: Proxy n -> HList (ru ': us) -> e Source #

class SortForRecordUS x x' | x -> x' where Source #

Reorders a Record such that the RecordUS made from it takes up less space

Bad has alternating Double and Int fields

>>> bad
Record{x=1.0,i=2,y=3.0,j=4}

4 arrays containing one element each are needed when this Record is stored as a RecordUS

>>> recordToRecordUS bad
RecordUS H[RecordU (array (0,0) [(0,1.0)]),RecordU (array (0,0) [(0,2)]),RecordU (array (0,0) [(0,3.0)]),RecordU (array (0,0) [(0,4)])]

It is possible to sort the record

>>> sortForRecordUS bad
Record{x=1.0,y=3.0,i=2,j=4}

This allows the same content to be stored in two unboxed arrays

>>> recordToRecordUS (sortForRecordUS bad)
RecordUS H[RecordU (array (0,1) [(0,1.0),(1,3.0)]),RecordU (array (0,1) [(0,2),(1,4)])]

Instances

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

Defined in Data.HList.RecordU

Methods

sortForRecordUS :: Record '[] -> Record '[] Source #

(HPartitionEq EqTagValue x (x ': xs) xi xo, SortForRecordUS xo xo', sorted ~ HAppendListR xi xo', HAppendList xi xo') => SortForRecordUS (x ': xs) sorted Source # 
Instance details

Defined in Data.HList.RecordU

Methods

sortForRecordUS :: Record (x ': xs) -> Record sorted Source #

type family GetElemTy (x :: [*]) :: * Source #

Instances

Instances details
type GetElemTy (Tagged label v ': rest) Source # 
Instance details

Defined in Data.HList.RecordU

type GetElemTy (Tagged label v ': rest) = v

data RecordU l Source #

A type which behaves similarly to Record, except all elements must fit in the same UArray. A consequence of this is that RecordU has the following properties:

  • it is strict in the element types
  • it cannot do type-changing updates of RecordU, except if the function applies to all elements
  • it probably is slower to update the very first elements of the RecordU

The benefit is that lookups should be faster and records should take up less space. However benchmarks done with a slow HNat2Integral do not suggest that RecordU is faster than Record.

Instances

Instances details
(ApplyAB f (GetElemTy x) (GetElemTy y), IArray UArray (GetElemTy y), IArray UArray (GetElemTy x)) => HMapAux RecordU f x y Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hMapAux :: f -> RecordU x -> RecordU y Source #

(r ~ r', v ~ GetElemTy r, HFindLabel l r n, HNat2Integral n, IArray UArray v, HasField l (Record r') v) => HUpdateAtLabel RecordU (l :: k) v r r' Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hUpdateAtLabel :: Label l -> v -> RecordU r -> RecordU r' Source #

(s ~ t, a ~ b, IArray UArray a, a ~ GetElemTy s, HLensCxt x RecordU s t a b) => Labelable (x :: k) RecordU s t a b Source #

make a Lens' (RecordU s) a

Instance details

Defined in Data.HList.RecordU

Associated Types

type LabelableTy RecordU :: LabeledOpticType Source #

Methods

hLens' :: Label x -> LabeledOptic x RecordU s t a b Source #

(IArray UArray v, v ~ GetElemTy ls, HFindLabel l ls n, HNat2Integral n) => HasField (l :: k) (RecordU ls) v Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hLookupByLabel :: Label l -> RecordU ls -> v Source #

(RecordValues lv, HList2List (RecordValuesR lv) v, HFindMany (LabelsOf lv) (LabelsOf r) ixs, IArray UArray v, v ~ GetElemTy r, HNats2Integrals ixs) => HUpdateMany lv (RecordU r) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

hUpdateMany :: Record lv -> RecordU r -> RecordU r Source #

Read (UArray Int (GetElemTy l)) => Read (RecordU l) Source # 
Instance details

Defined in Data.HList.RecordU

Show (UArray Int (GetElemTy l)) => Show (RecordU l) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

showsPrec :: Int -> RecordU l -> ShowS #

show :: RecordU l -> String #

showList :: [RecordU l] -> ShowS #

Eq (UArray Int (GetElemTy l)) => Eq (RecordU l) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

(==) :: RecordU l -> RecordU l -> Bool #

(/=) :: RecordU l -> RecordU l -> Bool #

Ord (UArray Int (GetElemTy l)) => Ord (RecordU l) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

compare :: RecordU l -> RecordU l -> Ordering #

(<) :: RecordU l -> RecordU l -> Bool #

(<=) :: RecordU l -> RecordU l -> Bool #

(>) :: RecordU l -> RecordU l -> Bool #

(>=) :: RecordU l -> RecordU l -> Bool #

max :: RecordU l -> RecordU l -> RecordU l #

min :: RecordU l -> RecordU l -> RecordU l #

HMapUnboxF xs us => HMapUnboxF (HList x ': xs) (RecordU x ': us) Source # 
Instance details

Defined in Data.HList.RecordU

type LabelableTy RecordU Source # 
Instance details

Defined in Data.HList.RecordU

class HMapUnboxF (xs :: [*]) (us :: [*]) | xs -> us, us -> xs Source #

proof that hMap UnboxF :: r xs -> r us can determine xs from us and us from xs

Instances

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

Defined in Data.HList.RecordU

HMapUnboxF xs us => HMapUnboxF (HList x ': xs) (RecordU x ': us) Source # 
Instance details

Defined in Data.HList.RecordU

data EqTagValue Source #

Instances

Instances details
HEqByFn EqTagValue Source # 
Instance details

Defined in Data.HList.RecordU

(txv ~ Tagged x v, tyw ~ Tagged y w, HEq v w b) => HEqBy EqTagValue (txv :: Type) (tyw :: Type) b Source # 
Instance details

Defined in Data.HList.RecordU

class RecordUSCxt (x :: [*]) (u :: [*]) | x -> u, u -> x Source #

connect the unpacked x representation with the corresponding list of RecordU u representation.

Instances

Instances details
(HGroupBy EqTagValue x g, HMapUnboxF g u) => RecordUSCxt x u Source #

the only instance

Instance details

Defined in Data.HList.RecordU

data RecordUS (x :: [*]) Source #

RecordUS is stored as a HList of RecordU to allow the RecordUS to contain elements of different types, so long all of the types can be put into an unboxed array (UArray).

It is advantageous (at least space-wise) to sort the record to keep elements with the same types elements adjacent. See SortForRecordUS for more details.

Instances

Instances details
(HFindLabel l r n, HLookupByHNatUS n u (Tagged l v), HasField l (Record r) v, RecordUSCxt r u) => HasField (l :: k) (RecordUS r) v Source #

works expected. See examples attached to bad.

Instance details

Defined in Data.HList.RecordU

Methods

hLookupByLabel :: Label l -> RecordUS r -> v Source #

(RecordUSCxt x u, Show (HList u)) => Show (RecordUS x) Source # 
Instance details

Defined in Data.HList.RecordU

Methods

showsPrec :: Int -> RecordUS x -> ShowS #

show :: RecordUS x -> String #

showList :: [RecordUS x] -> ShowS #

unboxedS :: forall {g1 :: [Type]} {u1 :: [Type]} {g2 :: [Type]} {u2 :: [Type]} {x1 :: [Type]} {x2 :: [Type]} {p} {f}. (HMapUnboxF g1 u1, HMapUnboxF g2 u2, HGroupBy EqTagValue x1 g1, HGroupBy EqTagValue x2 g2, Profunctor p, Functor f, HConcatFD g1 x1, SameLength' u2 g2, SameLength' g2 u2, SameLength' u1 g1, SameLength' g1 u1, HMapAux HList UnboxF g2 u2, HMapAux HList BoxF u1 g1) => p (RecordUS x2) (f (RecordUS x1)) -> p (Record x2) (f (Record x1)) Source #

Iso (Record x) (Record y) (RecordUS x) (RecordUS y)

unboxedS' :: forall {g :: [Type]} {u :: [Type]} {x :: [Type]} {p} {f}. (HMapUnboxF g u, HGroupBy EqTagValue x g, Profunctor p, Functor f, HConcatFD g x, SameLength' u g, SameLength' g u, HMapAux HList UnboxF g u, HMapAux HList BoxF u g) => p (RecordUS x) (f (RecordUS x)) -> p (Record x) (f (Record x)) Source #

Iso' (Record x) (RecordUS x)

hMapRU :: HMapCxt RecordU f x y => f -> RecordU x -> RecordU y Source #

hMap specialized to RecordU

unboxed :: forall x y f p. (Profunctor p, Functor f, RecordToRecordU x, RecordUToRecord y) => (RecordU x `p` f (RecordU y)) -> Record x `p` f (Record y) Source #

Iso (Record x) (Record y) (RecordU x) (RecordU y)

unboxed' :: forall {p} {f} {y :: [Type]} {n :: HNat}. (Profunctor p, Functor f, RecordValues y, HList2List (RecordValuesR y) (GetElemTy y), KnownNat (HNat2Nat n), HLengthEq1 y n, HLengthEq2 y n, IArray UArray (GetElemTy y), SameLength' (HReplicateR n ()) y, HMapAux HList TaggedFn (RecordValuesR y) y) => p (RecordU y) (f (RecordU y)) -> p (Record y) (f (Record y)) Source #

Iso' (Record x) (RecordU x)

makeLabels :: [String] -> Q [Dec] Source #

Labels like Data.HList.Label5.

The following TH declaration splice should be placed at top-level, before the created values are used. Enable -XTemplateHaskell too.

 makeLabels ["getX","getY","draw","X"]

should expand into the following declarations

data LabelGetX deriving Typeable
data LabelGetY deriving Typeable
data LabelDraw deriving Typeable
data LabelX deriving Typeable
getX = Label :: Label LabelGetX
getY = Label :: Label LabelGetY
draw = Label :: Label LabelDraw
x    = Label :: Label LabelX

makeLabels3 Source #

Arguments

:: String

namespace

-> [String]

labels

-> Q [Dec] 

makeLabels6 :: [String] -> Q [Dec] Source #

for Data.HList.Label6

makeLabels6 ["x","y"]

is a shortcut for

x = Label :: Label "x"
y = Label :: Label "y"

makeLabelable :: String -> Q [Dec] Source #

makeLabelable "x y z" expands out to

x = hLens' (Label :: Label "x")
y = hLens' (Label :: Label "y")
z = hLens' (Label :: Label "z")

Refer to Data.HList.Labelable for usage.

class HasFieldPath (needJust :: Bool) (ls :: [*]) r v | needJust ls r -> v Source #

Minimal complete definition

hLookupByLabelPath1

Instances

Instances details
HasFieldPath 'False ('[] :: [Type]) v v Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy 'False -> Label '[] -> v -> v Source #

HasFieldPath 'True ('[] :: [Type]) v (Maybe v) Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy 'True -> Label '[] -> v -> Maybe v Source #

(HasField l (Record r) u, HasFieldPath needJust ls u v) => HasFieldPath needJust (Label l ': ls) (Record r) v Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Record r -> v Source #

(HasField l (Variant r) (Maybe u), HasFieldPath 'True ls u (Maybe v)) => HasFieldPath needJust (Label l ': ls) (Variant r) (Maybe v) Source # 
Instance details

Defined in Data.HList.Dredge

Methods

hLookupByLabelPath1 :: Proxy needJust -> Label (Label l ': ls) -> Variant r -> Maybe v Source #

dredge :: forall {k1} {k2} {r} {ns :: [[Type]]} {xs :: [Type]} {p} {v} {fb :: k1} {rft :: k1} {vs :: [Type]} {ns1 :: [[Type]]} {vs1 :: [Type]} {l :: k2} {ns2 :: [[Type]]} {x}. (MapFieldTree (TryCollectionListTF r) ns, LabelablePath xs (p v fb) (p r rft), SameLength' ns vs, SameLength' ns1 vs1, SameLength' vs ns, SameLength' vs1 ns1, MapFieldTreeVal r (TryCollectionListTF r) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 v vs1 ns1 ns2, HGuardNonNull (NamesDontMatch r ns l) ns1, HSingleton (NonUnique r v l) (TypesDontMatch r ns1 vs1 v) ns2 xs, EnsureLabel x (Label l)) => x -> p v fb -> p r rft Source #

Using HListPP syntax for short hand, dredge `foo expands out to something like `path . `to . `foo, with the restriction that there is only one possible `path . `to which leads to the label foo.

For example, if we have the following definitions,

type BVal a = Record '[Tagged "x" a, Tagged "a" Char]
type R a = Record  [Tagged "a" Int, Tagged "b" (BVal a)]
type V a = Variant [Tagged "a" Int, Tagged "b" (BVal a)]
lx = Label :: Label "x"

Then we have:

dredge `x :: Lens (R a) (R b) a b
dredge lx :: Lens (R a) (R b) a b
dredge `x :: Traversal (V a) (V b) a b -- there were only variants along the path we'd get a Prism
dredge lx :: Traversal (V a) (V b) a b
result-type directed operations are supported

There are two ways to access a field with tag a in the R type defined above, but they result in fields with different types being looked up:

`a        :: Lens' (R a) Char
`b . `a   :: Lens' (R a) Int

so provided that the result type is disambiguated by the context, the following two types can happen

dredge `a :: Lens' (R a) Char
dredge `a :: Lens' (R a) Int
TIP & TIC

type indexed collections are allowed along those paths, but as explained in the Labelable instances, only simple optics (Lens' Prism' Traversal' ) are produced. dredgeTI' works better if the target is a TIP or TIC

dredge' :: forall {k1} {k2} {s} {ns :: [[Type]]} {xs :: [Type]} {p} {a} {f :: Type -> k1} {vs :: [Type]} {ns1 :: [[Type]]} {vs1 :: [Type]} {l :: k2} {ns2 :: [[Type]]} {x}. (MapFieldTree (TryCollectionListTF s) ns, LabelablePath xs (p a (f a)) (p s (f s)), SameLength' ns vs, SameLength' ns1 vs1, SameLength' vs ns, SameLength' vs1 ns1, MapFieldTreeVal s (TryCollectionListTF s) vs, FilterLastEq (Label l) ns ns ns1, FilterLastEq (Label l) ns vs vs1, FilterVEq1 a vs1 ns1 ns2, HGuardNonNull (NamesDontMatch s ns l) ns1, HSingleton (NonUnique s a l) (TypesDontMatch s ns1 vs1 a) ns2 xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s) Source #

dredge except a simple (s ~ t, a ~ b) optic is produced

dredgeND :: forall {k1} {k2} {xs :: [Type]} {p} {a} {fb :: k1} {r} {rft :: k1} {ns :: [[Type]]} {l :: k2} {ns' :: [[Type]]} {x}. (LabelablePath xs (p a fb) (p r rft), MapFieldTree (TryCollectionListTF r) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r l) (NamesDontMatch r ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a fb -> p r rft Source #

dredgeND (named directed only) is the same as dredge, except the result type (a) is not used when the label would otherwise be ambiguous. dredgeND might give better type errors, but otherwise there should be no reason to pick it over dredge

dredgeND' :: forall {k1} {k2} {xs :: [Type]} {p} {a} {f :: Type -> k1} {s} {ns :: [[Type]]} {l :: k2} {ns' :: [[Type]]} {x}. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' s l) (NamesDontMatch s ns l) ns' xs, EnsureLabel x (Label l)) => x -> p a (f a) -> p s (f s) Source #

dredgeND except a simple (s ~ t, a ~ b) optic is produced

dredgeTI' :: forall {k} {xs :: [Type]} {p} {a} {f :: Type -> k} {s} {ns :: [[Type]]} {ns' :: [[Type]]} {q}. (LabelablePath xs (p a (f a)) (p s (f s)), MapFieldTree (TryCollectionListTF s) ns, FilterLastEq (Label a) ns ns ns', HSingleton (NonUnique' s a) (NamesDontMatch s ns a) ns' xs) => q a -> p a (f a) -> p s (f s) Source #

The same as dredgeND', except intended for TIP/TICs because the assumption is made that l ~ v for the Tagged l v elements. In other words, ticPrism' and tipyLens' could usually be replaced by

dredgeTI' :: _ => Label a -> Lens'  (TIP s) a
dredgeTI' :: _ => Label a -> Prism' (TIC s) a

where we might have s ~ '[Tagged a a, Tagged b b]

hLookupByLabelDredge :: forall {k} {ls :: [Type]} {r1} {r2} {v} {ns :: [[Type]]} {l :: k} {ns' :: [[Type]]}. (HasFieldPath 'False ls (r1 r2) v, MapFieldTree (TryCollectionListTF r2) ns, FilterLastEq (Label l) ns ns ns', HSingleton (NonUnique' r2 l) (NamesDontMatch r2 ns l) ns' ls) => Label l -> r1 r2 -> v Source #

module Data.STRef

module Data.IORef

concrete :: MonadFix m => (a -> m a) -> a -> m a Source #

(#) :: HasField l r v => r -> Label l -> v infixr 9 Source #