barbies-th: Create strippable HKD via TH

[ bsd3, data, data-structures, generics, library ] [ Propose Tags ]

Please see Data.Barbie.TH


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0, 0.1, 0.1.1, 0.1.2, 0.1.3, 0.1.4, 0.1.5, 0.1.7, 0.1.8, 0.1.9, 0.1.10, 0.1.11
Change log CHANGELOG.md
Dependencies barbies (>=2.0.1 && <2.1), base (>=4.12), split (>=0.2 && <0.3), template-haskell (>=2.14 && <2.17) [details]
License BSD-3-Clause
Copyright Copyright (c) 2020 Fumiaki Kinoshita
Author Fumiaki Kinoshita
Maintainer fumiexcel@gmail.com
Category Data, Generics
Bug tracker https://github.com/fumieval/barbies-th
Uploaded by FumiakiKinoshita at 2020-10-28T02:29:37Z
Distributions
Reverse Dependencies 2 direct, 3 indirect [details]
Downloads 3532 total (61 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-10-28 [all 1 reports]

Readme for barbies-th-0.1.7

[back to package description]

barbies-th

Hackage Haskell CI

A wrapper library for barbies to generate strippable HKDs. It transforms the following declaration

declareBareB [d|
  data Foo = Foo
    { foo :: Int
    , bar :: String
    }  |]

into:

data Foo sw h = Foo
    { foo :: Wear sw h Int,
    , bar :: Wear sw h String
    }
instance BareB Foo
instance FieldNamesB (Foo Covered) where
  bfieldNames = Foo (Const "foo") (Const "bar")
instance ProductB (Foo Covered) where
  bprod (Foo xfoo xbar) (Foo yfoo ybar)
    = Foo (Pair xfoo yfoo) (Pair xbar ybar)
instance FunctorB (Foo Covered) where ...
instance TraversableB (Foo Covered) where ...
instance ConstraintsB (Foo Covered)
instance ProductBC (Foo Covered)

Typically you need the following extensions to make declareBareB work:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

GHC sometimes takes very long time to compile code with generically derived instances, and it often fails to inline functions properly too. This package generates most instance methods by TH, reducing large amount of compilation time of the declarations and use sites.

Unlike higgledy which relies on in-memory representation using GHC.Generic, you don't have to worry about the performance, and you can benefit from various language features (e.g. -Wmissing-fields, RecordWildCards etc) even in higher-kinded form.

Deriving pass-through

stock deriving does not work on HKDs. Instead, it transforms deriving clauses into standalone ones via the Barbie wrapper, as well as ones for the Bare counterpart. For example,

data Foo = ... deriving (Show, Eq)

generates

deriving instance Show (Foo Bare Identity)
deriving instance Eq (Foo Bare Identity)
deriving via Barbie (Foo Covered) h instance Show (Barbie (Foo Covered) h) => Show (Foo Covered h)
deriving via Barbie (Foo Covered) h instance Eq (Barbie (Foo Covered) h) => Eq (Foo Covered h)