hetero-dict-0.1.1.0: Fast heterogeneous data structures

Safe HaskellNone
LanguageHaskell2010

Data.Hetero.Dict

Contents

Description

Fast read-only heterogeneous array.

This module is extracted from web-routing, orginally desgined for high performance type safe routing. The basic idea is:

  1. Construct a heterogeneous linked-list is O(n), since prepend is O(1).
  2. Convert it into a heterogeneous array in O(n).
  3. Following access will be a simple O(1) array indexing, with index computed at compile time so you can't get missing keys.

In theory, it's faster than linked-list based data structures when n is large, but it needs more benchmark to be sure.

Typical usage: a heterogeneous lookup table, indexed by type level string.

> :set -XDataKinds -XQuasiQuotes
> let d = mkDict . add [key|foo|] 12 . add [key|bar|] "baz" $ emptyStore
> get [key|foo|] d
12
> get [key|bar|] d
"baz"

Synopsis

Store

data Store kvs Source #

Heterogeneous linked-list with a size field.

use mkDict to convert it into a Dict.

Constructors

Store 

Fields

Instances

ShowDict kvs => Show (Store kvs) Source # 

Methods

showsPrec :: Int -> Store kvs -> ShowS #

show :: Store kvs -> String #

showList :: [Store kvs] -> ShowS #

emptyStore :: Store '[] Source #

An empty Store

add :: NotHasKey k kvs => Proxy k -> v -> Store kvs -> Store ((k := v) ': kvs) Source #

O(1) add key value pair to Store.

> let a = add [key|foo|] (12 :: Int) emptyStore
> a
Store {foo = 12 :: Int}
> add [key|bar|] "baz" a
Store {bar = "baz" :: [Char], foo = 12 :: Int}

Dict

data Dict kvs Source #

Read-Only heterogeneous array.

The underline data structure is a boxed array, support get operation only.

Instances

ShowDict kvs => Show (Dict kvs) Source # 

Methods

showsPrec :: Int -> Dict kvs -> ShowS #

show :: Dict kvs -> String #

showList :: [Dict kvs] -> ShowS #

mkDict' :: forall s kvs. Store kvs -> ST s (Dict kvs) Source #

O(n) convert a Store into a Dict inside ST monad.

mkDict :: Store kvs -> Dict kvs Source #

O(n) convert Store to Dict.

class InDict k v kvs | k kvs -> v Source #

Constraint ensure Dict must contain k-v pair.

Minimal complete definition

get'

Instances

(InDict k v kvs, (~) GetResult (Index i) (Ix k ((:) (KV *) ((:=) * k' v') kvs)), KnownNat i) => InDict k v ((:) (KV *) ((:=) * k' v') kvs) Source # 

Methods

get' :: Proxy Symbol k -> Dict ((KV * ': (* := k') v') kvs) -> v

InDict k v ((:) (KV *) ((:=) * k v) kvs) Source # 

Methods

get' :: Proxy Symbol k -> Dict ((KV * ': (* := k) v) kvs) -> v

get :: InDict k v kvs => Proxy k -> Dict kvs -> v Source #

O(1) get value using associated key from Dict.

re-export from KVList

key :: QuasiQuoter Source #

Quoter for constructing string literal proxy.

[key|foo|] == (Proxy :: Proxy "foo")

data KV v Source #

(kind) key-value pair

Constructors

Symbol := v 

Instances

(InDict k v kvs, (~) GetResult (Index i) (Ix k ((:) (KV *) ((:=) * k' v') kvs)), KnownNat i) => InDict k v ((:) (KV *) ((:=) * k' v') kvs) Source # 

Methods

get' :: Proxy Symbol k -> Dict ((KV * ': (* := k') v') kvs) -> v

InDict k v ((:) (KV *) ((:=) * k v) kvs) Source # 

Methods

get' :: Proxy Symbol k -> Dict ((KV * ': (* := k) v) kvs) -> v

(InDict k v kvs, (~) GetResult (Index i) (Ix k ((:) (KV *) ((:=) * k' v') kvs)), KnownNat i) => InDict k v ((:) (KV *) ((:=) * k' v') kvs) Source # 

Methods

get' :: Proxy Symbol k -> DynDict ((KV * ': (* := k') v') kvs) -> v

modify' :: Proxy Symbol k -> (v -> v) -> DynDict ((KV * ': (* := k') v') kvs) -> DynDict ((KV * ': (* := k') v') kvs)

InDict k v ((:) (KV *) ((:=) * k v) kvs) Source # 

Methods

get' :: Proxy Symbol k -> DynDict ((KV * ': (* := k) v) kvs) -> v

modify' :: Proxy Symbol k -> (v -> v) -> DynDict ((KV * ': (* := k) v) kvs) -> DynDict ((KV * ': (* := k) v) kvs)

(KnownSymbol k, ToJSON v, ToJSON (DynDict kvs)) => ToJSON (DynDict ((:) (KV *) ((:=) * k v) kvs)) # 

Methods

toJSON :: DynDict ((KV * ': (* := k) v) kvs) -> Value #

toEncoding :: DynDict ((KV * ': (* := k) v) kvs) -> Encoding #

ToJSON (DynDict ([] (KV *))) # 
(KnownSymbol k, FromJSON v, FromJSON (DynDict kvs)) => FromJSON (DynDict ((:) (KV *) ((:=) * k v) kvs)) # 

Methods

parseJSON :: Value -> Parser (DynDict ((KV * ': (* := k) v) kvs)) #

FromJSON (DynDict ([] (KV *))) # 

Methods

parseJSON :: Value -> Parser (DynDict [KV *]) #

ShowDict ([] (KV *)) Source # 

Methods

showDict :: Int -> Dict [KV *] -> [(String, String, TypeRep)] Source #

(KnownSymbol k, Typeable * v, Show v, ShowDict kvs) => ShowDict ((:) (KV *) ((:=) * k v) kvs) Source # 

Methods

showDict :: Int -> Dict ((KV * ': (* := k) v) kvs) -> [(String, String, TypeRep)] Source #

data KVList kvs where Source #

A simple heterogeneous kv linked-list.

Constructors

Cons :: !v -> KVList kvs -> KVList ((k := v) ': kvs) 
Empty :: KVList '[] 

type NotHasKey k kvs = AddKey k kvs ~ HasKey k Source #

Constraint ensure a key will be inserted into Store.

type Ix k kvs = Ix' 0 k kvs Source #

Indexing a key at compile time.

helpers

class ShowDict kvs where Source #

Helper class for defining store's Show instance.

Minimal complete definition

showDict

Methods

showDict :: Int -> Dict kvs -> [(String, String, TypeRep)] Source #

Instances

ShowDict ([] (KV *)) Source # 

Methods

showDict :: Int -> Dict [KV *] -> [(String, String, TypeRep)] Source #

(KnownSymbol k, Typeable * v, Show v, ShowDict kvs) => ShowDict ((:) (KV *) ((:=) * k v) kvs) Source # 

Methods

showDict :: Int -> Dict ((KV * ': (* := k) v) kvs) -> [(String, String, TypeRep)] Source #