json-tracer-0.0.1.2: A polymorphic, type-safe, json-structured tracing library

Copyright(c) Taku Terao 2017
LicenseBSD3
Maintainerautotaker@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Data.PolyDict

Description

Type-safe, polymorphic dictionary.

Synopsis

Documentation

type family DictValue v :: Constraint where ... Source #

DictValue is the constraint for values can be inserted into Dict

Equations

DictValue v = (Eq v, Show v, ToJSON v) 

type family Assoc n (k :: Symbol) Source #

Assoc n k defines the type of value associated with key k. Parameter n defines the namespace for dictionary fields. For example:

data Log
type instance Assoc Log "argments" = [String]
type instance Assoc Log "count" = Int

Then Dict Log is a dictionary type with (at least) two fields "arguments" and "count".

One can access the fields by using insert and lookup.

>>> insert #count 0 (empty :: Dict Log)
{"count": 0}
>>> lookup #count (insert #count 0 (empty :: Dict Log))
Just 0

Or by using lenses:

>>> import Lens.Micro
>>> (empty :: Dict Log) & (access #count ?~ 1) . (access #arguments ?~ ["a","b","c"])
{"arguments": ["a","b","c"], "count": 1}

data Dict n Source #

A polymorphic, type-safe dictinary type where the parameter n represents the namespace of dictionary fields.

Instances

Eq (Dict n) Source # 

Methods

(==) :: Dict n -> Dict n -> Bool #

(/=) :: Dict n -> Dict n -> Bool #

Show (Dict n) Source # 

Methods

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

show :: Dict n -> String #

showList :: [Dict n] -> ShowS #

ToJSON (Dict n) Source # 

data Key k Source #

The type of keys. With the OverloadedLabels extenstion, #foo is the key for field "foo"

Instances

(~) Symbol k k' => IsLabel k (Key k') Source # 

Methods

fromLabel :: Proxy# Symbol k -> Key k' #

lookup :: (KnownSymbol k, DictValue v, Assoc n k ~ v) => Key k -> Dict n -> Maybe v Source #

Return the value associated with the key.

insert :: (KnownSymbol k, DictValue v, Assoc n k ~ v) => Key k -> v -> Dict n -> Dict n Source #

Insert the value at the specified key of the dictionary

access :: forall n k v. (KnownSymbol k, DictValue v, Assoc n k ~ v) => Key k -> Lens' (Dict n) (Maybe v) Source #

Give the lens accessing to the value associated with the key.

access' :: forall n k v. (KnownSymbol k, DictValue v, Assoc n k ~ v) => Key k -> v -> Lens' (Dict n) v Source #

Same as access but requires the default value.

empty :: Dict n Source #

Return the empty dictionary.