HList-0.5.3.0: Heterogeneous lists
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HList.HList

Description

The HList library

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

Basic declarations for typeful heterogeneous lists.

Synopsis

Heterogeneous type sequences

There are three sensible ways to define HLists:

data HList (l::[*]) where
    HNil  :: HList '[]
    HCons :: e -> HList l -> HList (e ': l)

This ensures that sequences can only be formed with Nil and Cons. The argument to HList is a promoted lists (kind [*]), which has a more attractive syntax.

Earlier versions of HList used an algebraic data type:

data HCons a b = HCons a b
data HNil = HNil

Disadvantages:

  • values with types like HCons Int Double to be created, which are nonsense to the functions in HList
  • some recursive functions do not need a class with the GADT. For example:
   hInit :: HListGADT (x ': xs) -> HListGADT (HInit (x ': xs))
   hInit (HCons x xs@(HCons _ _)) = HCons x (hInit xs)
   hInit (HCons _ HNil) = HNil

   type family HInit (xs :: [k]) :: [k]
 

but without the GADT, hInit is written as in a class, which complicates inferred types

Advantages

  • lazy pattern matches are allowed, so lazy pattern matching on a value undefined :: HList [a,b,c] can create the spine of the list. hProxies avoids the use of undefined, but a slightly more complicated class context has to be written or inferred.
  • type inference is better if you want to directly pattern match see stackoverflow post here
  • better pattern exhaustiveness checking (as of ghc-7.8)
  • standalone deriving works
  • Data.Coerce.coerce works because the parameters have role representational, not nominal as they are for the GADT and data family. Probably the GADT/type family actually do have a representational role: http://stackoverflow.com/questions/24222552/does-this-gadt-actually-have-type-role-representational

The data family version (currently used) gives the same type constructor HList :: [*] -> * as the GADT, while pattern matching behaves like the algebraic data type. Furthermore, nonsense values like HCons 1 2 :: HCons Int Int cannot be written with the data family.

A variation on the data family version is

data instance HList '[] = HNil
newtype instance HList (x ': xs) = HCons1 (x, HList xs)
pattern HCons x xs = HCons1 (x, xs)

This allows HList to have a nominal role, but on the other hand the PatternSynonym is not supported with ghc-7.6 and exhaustiveness checking is not as good (warnings for _ being unmatched)

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

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 #

type HProxies xs = HProxiesFD xs (AddProxy xs) Source #

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 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

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 #

Basic list functions

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 #

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 #

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)

hLength :: HLengthEq l n => HList l -> Proxy n Source #

Append

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'

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 #

Alternative append

append' :: [a] -> [a] -> [a] Source #

hAppend' below is implemented using the same idea

hAppend' :: HFoldr FHCons v l r => HList l -> v -> r Source #

Alternative implementation of hAppend. Demonstrates HFoldr

data FHCons Source #

Constructors

FHCons 

Instances

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

Historical append

The original HList code is included below. In both cases we had to program the algorithm twice, at the term and the type levels.

The class HAppend
class HAppend l l' l'' | l l' -> l''
 where
  hAppend :: l -> l' -> l''
The instance following the normal append
instance HList l => HAppend HNil l l
 where
  hAppend HNil l = l

instance (HList l, HAppend l l' l'')
      => HAppend (HCons x l) l' (HCons x l'')
 where
  hAppend (HCons x l) l' = HCons x (hAppend l l')

Reversing HLists

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

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 #

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

A nicer notation for lists

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

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 #

examples

The classes above allow the third (shortest) way to make a list (containing a,b,c) in this case

list = a `HCons` b `HCons` c `HCons` HNil
list = a .*. b .*. c .*. HNil
list = hEnd $ hBuild a b c
>>> let x = hBuild True in hEnd x
H[True]
>>> let x = hBuild True 'a' in hEnd x
H[True,'a']
>>> let x = hBuild True 'a' "ok" in hEnd x
H[True,'a',"ok"]

hBuild can also produce a Record, such that

hBuild x y ^. from unlabeled

can also be produced using

hEndR $ hBuild x y

historical

the show instance has since changed, but these uses of hBuild/hEnd still work

HList> let x = hBuild True in hEnd x
HCons True HNil
HList> let x = hBuild True 'a' in hEnd x
HCons True (HCons 'a' HNil)
HList> let x = hBuild True 'a' "ok" in hEnd x
HCons True (HCons 'a' (HCons "ok" HNil))
HList> hEnd (hBuild (Key 42) (Name "Angus") Cow (Price 75.5))
HCons (Key 42) (HCons (Name "Angus") (HCons Cow (HCons (Price 75.5) HNil)))
HList> hEnd (hBuild (Key 42) (Name "Angus") Cow (Price 75.5)) == angus
True

folds

foldr

Consume a heterogenous list.

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

foldl

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 #

unfolds

unfold

Produce a heterogenous list. Uses the more limited Apply instead of App since that's all that is needed for uses of this function downstream. Those could in principle be re-written.

hUnfold :: forall {f} {a} {z :: [Type]}. (HUnfoldFD f (ApplyR f a) z, Apply f a) => f -> a -> HList z Source #

type HUnfold p s = HUnfoldR p (ApplyR p s) 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 res = HUnfoldFD p (ApplyR p res) (HUnfold p res) 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 #

replicate

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 #

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

iterate

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 #

concat

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"]

hConcat :: HConcat xs => HList xs -> HList (HConcatR xs) Source #

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 family UnHList a :: [*] Source #

Instances

Instances details
type UnHList (HList a) Source # 
Instance details

Defined in Data.HList.HList

type UnHList (HList a) = a

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 #

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 #

traversing HLists

producing HList

map

It could be implemented with hFoldr, as we show further below

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 #

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

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 #

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

class HMapAux (r :: [*] -> *) f (x :: [*]) (y :: [*]) where Source #

Methods

hMapAux :: SameLength x y => f -> r x -> r y Source #

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 #

alternative implementation

currently broken

newtype MapCar f Source #

Constructors

MapCar f 

Instances

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

hMapMapCar :: HFoldr (MapCar f) (HList '[]) l l' => f -> HList l -> l' Source #

Same as hMap only a different implementation.

appEndo . mconcat . map Endo

hComposeList :: HFoldr Comp (a -> a) l (t -> a) => HList l -> t -> a Source #

>>> let xs = length .*. (+1) .*. (*2) .*. HNil
>>> hComposeList xs "abc"
8

sequence

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 #

alternative implementation

hSequence2 :: forall {f} {l :: [Type]} {a}. (Applicative f, HFoldr (LiftA2 FHCons) (f (HList ('[] :: [Type]))) l (f a)) => HList l -> f a Source #

hSequence2 is not recommended over hSequence since it possibly doesn't allow inferring argument types from the result types. Otherwise this version should do exactly the same thing.

The DataKinds version needs a little help to find the type of the return HNil, unlike the original version, which worked just fine as

hSequence l = hFoldr ConsM (return HNil) l

producing homogenous lists

map (no sequencing)

This one we implement via hFoldr

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 #

type HMapOut f l e = HFoldr (Mapcar f) [e] l [e] Source #

hMapOut :: forall f e l. HMapOut f l e => f -> HList l -> [e] Source #

compare hMapOut f with hList2List . hMap f

mapM

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:

Ensure a list to contain HNats only

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

Membership tests

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

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

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))

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

hMember :: HMember e l b => Proxy e -> Proxy l -> Proxy b Source #

Another type-level membership test

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

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 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

Staged equality for lists

removed. use Typeable instead

Find an element in a set based on HEq

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 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 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

Membership test based on type equality

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

hTMember :: HTMember e l b => e -> HList l -> Proxy b Source #

Intersection based on HTMember

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

Convert between heterogeneous lists and homogeneous ones

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 #

list2HList :: HList2List l e => [e] -> Maybe (HList l) Source #

listAsHList :: forall {p} {f} {l :: [Type]} {e} {l :: [Type]} {e}. (Choice p, Applicative f, HList2List l e, HList2List l e) => p (HList l) (f (HList l)) -> p [e] (f [e]) 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

With HMaybe

Turn list in a list of justs

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 #

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.

Extract justs from list of maybes

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 #

alternative implementation

fromHJust2 :: HMapCxt r HFromJust a b => r a -> r b Source #

This implementation is shorter.

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 #

Annotated lists

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

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

Splitting by HTrue and HFalse

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 #

Splitting by Length

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 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 (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 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 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 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 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 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

take

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 #

drop

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 #

Conversion to and from tuples

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 #

hTuple :: forall {p} {f} {v :: [Type]} {a} {v :: [Type]} {b}. (Profunctor p, Functor f, HTuple v a, HTuple v b) => p a (f b) -> p (HList v) (f (HList v)) 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 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 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 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 #

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 #

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

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

partition

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 #

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 #

groupBy

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 #

span

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

zip

see alternative implementations in Data.HList.HZip

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 #

Monoid instance

helper functions

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 #

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