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

[ bsd3, control, library ] [ Propose Tags ]

This library provides a way of structured tracing, which are useful for logging call graphs.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.0.1.0, 0.0.1.1, 0.0.1.2, 0.0.2.0, 0.0.3.0
Change log CHANGELOG.md
Dependencies aeson (>=0.11), base (>=4.10 && <5), containers (>=0.5 && <0.6), ghc-prim (>=0.5 && <0.6), hashable (>=1.2.7 && <1.2.8), microlens (>0.4.0), microlens-ghc (>0.4.0), mtl (>=2.2 && <2.3), template-haskell (>=2.11), text (>=1.2.2), transformers (>=0.5 && <0.6), unordered-containers (>=0.2.8) [details]
License BSD-3-Clause
Copyright 2017 Taku Terao
Author Taku Terao
Maintainer autotaker@gmail.com
Category Control
Home page https://github.com/autotaker/json-tracer#readme
Source repo head: git clone https://github.com/autotaker/json-tracer
Uploaded by autotaker at 2018-05-11T06:29:55Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 3156 total (14 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-05-11 [all 1 reports]

Readme for json-tracer-0.0.3.0

[back to package description]

json-tracer

Type-safe polymorphic json-structured tracing library

hackage

This library provides two modules

  • Data.PolyDict: type-safe, polymorphic, and json-structured dictionary
  • Control.Monad.CTrace: a monad that enables contextual tracing

PolyDict

PolyDict is a hash dict like JSON, but it is typed. Dict n is a dictinary whose fields are typed accoding to Assoc n. That is, each field has type Key k (which is a proxy of type-level symbol k) and Assoc n k is the type of values associated with the key.

Basically, users define a data that represents the namespace of the Dict. For example:

data Main

Then, one can define the type of Dict n by adding rules for type family Assoc n k like this:

type instance Assoc Main "elapsed_time" = NominalDiffTime
type instance Assoc Main "tag" = String

The RHS type of the Assoc n k must satisfy the DictValue v constraint.

type family DictValue v :: Constraint where
    DictValue v = (Eq v, Show v, ToJSON v)

As far as the author knows, any ToJSON v value satisfy this constraint.

Note: Dict n is allowed as the RHS type as Dict n satisfies the DictValue constraint. Hence recursive structures can be handled.

Since the definition of type family is open, users don't have to define all rules at the same module. It's totally free to add other fields on demand, as long as there are no conflicting keys. When such confliction occurs, the compiler reports it as an error.

type instance Assoc Main "tag" = Int 
-- this would be compile error because the key "tag" is conflicting to the previous definition.

Values in Dict are obtained and updated by lookup and insert function.

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

With the OverloadedLabels extention, user can write #foo as the key for the field "foo".

Examples

ghci> let v = insert #tag "sample" empty 
ghci> v
{"tag": "sample"}
ghci> lookup #tag v
Just "sample"
ghci> lookup #elapsed_time v
Nothing

Instead, lenses can be used to access thouse fields with access function.

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

Examples

ghci> let v = empty & access #tag ?~ "sample"
ghci> v
{"tag": "sample"}
ghci> v ^. access #tag
Just "sample"

Tracer Monad

TracerT c m a is the type of a monad transformer that enables contextual tracing. update and zoom operations can be performed in this monad transformer.

update is the action to modifies the value of context.

update :: Monad m => (c -> c) -> TracerT c m ()

For example, you can count the number of calls of function f by inserting update succ :: TracerT Int m () for each call of f.

Note: although you can modify the value, you cannot get the current value in this monad. This is intentional, to make it easy to disable tracing.

zoom is the action to change the context of tracing.

zoom :: ASetter' c c' -> TracerT c' m a -> TracerT c m a

Complete Example

{-# LANGUAGE TypeFamilies, DataKinds, OverloadedLabels #-}
import Data.PolyDict
import Control.Monad.CTrace
import Lens.Micro
import Control.Monad

data Main
data Sub

type instance Assoc Main "sub" = Dict Sub
type instance Assoc Sub  "count" = Int

subFunc :: Monad m => Int -> TracerT (Dict Sub) m ()
subFunc n = replicateM_ n (update (access' #count 0 %~ succ))

mainFunc :: Monad m => TracerT (Dict Main) m ()
mainFunc = zoom (access' #sub empty) (subFunc 42)

main :: IO ()
main = do
    (_,d) <- ioTracerT empty mainFunc
    print d
-- > {"sub": {"count": 42}}