generic-data-surgery: Surgery for generic data types

[ library, mit, other ] [ Propose Tags ]

Transform data types before passing them to generic functions.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.1.0, 0.3.0.0
Change log CHANGELOG.md
Dependencies base (>=4.9 && <5), first-class-families (>=0.2), generic-data (>=0.2) [details]
License MIT
Copyright 2018 Li-yao Xia
Author Li-yao Xia
Maintainer lysxia@gmail.com
Category Other
Home page https://github.com/Lysxia/generic-data-surgery#readme
Source repo head: git clone https://github.com/Lysxia/generic-data-surgery
Uploaded by lyxia at 2020-05-02T04:00:56Z
Distributions LTSHaskell:0.3.0.0, NixOS:0.3.0.0, Stackage:0.3.0.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 1947 total (21 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-05-02 [all 1 reports]

Readme for generic-data-surgery-0.2.1.0

[back to package description]

Surgery for generic data types Hackage Build Status

Modify, add, or remove constructors and fields in generic types, to be used with generic implementations.

Example

Here is a simple record type equipped with a checksum function:

data Foo = Foo { x, y, z :: Int }
  deriving (Eq, Generic, Show)

checksum :: Foo -> Checksum

Let's encode it as a JSON object with an extra "checksum" key, looking like this, where X, Y, Z are integers:

{ "x": X
, "y": Y
, "z": Z
, "checksum": X + Y + Z
}

We use genericParseJSON/genericToJSON to convert between JSON values and a generic 4-field record, and removeRField/insertRField to convert between that generic 4-field record and the 3-field Foo.

Remove field

When decoding, we check the checksum and then throw it away.

instance FromJSON Foo where
  parseJSON v = do

    r <- genericParseJSON defaultOptions v
    -- r: a generic 4-field record {x,y,z,checksum} (checksum at index 3).

    let (cs, f) = (fmap fromOR . removeRField @"checksum" @3 . toOR') r
    -- removeRField @"checksum" @3: split out the checksum field
    -- from the three other fields. (cs, f) :: (Checksum, Foo)

    if checksum f == cs then
      pure f
    else
      fail "Checksum failed"

Insert field

When encoding, we must compute the checksum to write it out. We put the checksum in a pair (checksum f, f) with the original record, and insertRField can then wrap it into a 4-field record passed into genericToJSON.

instance ToJSON Foo where
  toJSON f =
    (genericToJSON defaultOptions . fromOR' . insertRField @"checksum" @3 . fmap toOR)
      (checksum f, f)

See also the examples/ directory in the source repo.