type-level-kv-list-1.0.0: A module for hash map like object with type level keys.

Safe HaskellSafe
LanguageHaskell2010

Data.TypeLevelKVList

Contents

Description

This module supply a way to construct type safe key-value pair list and convenient operations for the type.

Synopsis

Constructors

We can create type level KV list as follows.

>>> :set -XDataKinds -XTypeOperators
>>> let sampleList = (namedVal "str" :: NamedVal String "foo") :. (namedVal 34 :: NamedVal Int "bar") :. Null
>>> type SampleList = NamedVal String "foo" :. NamedVal Int "bar" :. Null

type NamedVal v key = (Proxy key, v) Source #

A value with type level key.

namedVal :: v -> NamedVal v k Source #

A convenient function to construct type level KV list.

data a :. b infixr 8 Source #

Type level list cons.

Constructors

a :. b infixr 8 

Instances

(Eq b, Eq a) => Eq ((:.) a b) Source # 

Methods

(==) :: (a :. b) -> (a :. b) -> Bool #

(/=) :: (a :. b) -> (a :. b) -> Bool #

(Show b, Show a) => Show ((:.) a b) Source # 

Methods

showsPrec :: Int -> (a :. b) -> ShowS #

show :: (a :. b) -> String #

showList :: [a :. b] -> ShowS #

data Null Source #

Type level empty list.

Constructors

Null 

Instances

Eq Null Source # 

Methods

(==) :: Null -> Null -> Bool #

(/=) :: Null -> Null -> Bool #

Show Null Source # 

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

Operators

get :: HasKey list pkey (Lookup pkey list) => pkey -> list -> Lookup pkey list Source #

>>> get (Proxy :: Proxy "foo") sampleList
"str"
>>> get (Proxy :: Proxy "bar") sampleList
34
>>> get (Proxy :: Proxy "baz") sampleList
Null

type family Lookup pkey list where ... Source #

Type level lookup :: k -> [(k, a)] -> a.

Equations

Lookup pk ((pk, v) :. b) = v 
Lookup pk ((px, v) :. b) = Lookup pk b 
Lookup pk Null = Null 

keys :: NamedList layout => Proxy layout -> [String] Source #

>>> keys (Proxy :: Proxy SampleList)
["foo","bar"]

keys' :: NamedList k => k -> [String] Source #

>>> keys' sampleList
["foo","bar"]