vinyl-generics: Convert plain records to vinyl (and vice versa), generically.

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

Convert plain records to vinyl and vice versa, via GHC.Generics and generics-sop/records-sop.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0
Change log CHANGELOG.md
Dependencies base (>=4.7 && <5), generics-sop (>=0.3.2), records-sop (>=0.1.0.2), vinyl (>=0.10) [details]
License BSD-3-Clause
Copyright 2018 Gagandeep Bhatia
Author Gagandeep Bhatia
Maintainer gagandeepbhatia.in@gmail.com
Category Data, Generics
Home page https://github.com/VinylRecords/vinyl-generics
Source repo head: git clone https://github.com/VinylRecords/vinyl-generics
Uploaded by GagandeepBhatia at 2019-02-19T16:34:12Z
Distributions
Downloads 644 total (12 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for vinyl-generics-0.1.0.0

[back to package description]

vinyl-generics

Build Status

Convert plain Haskell records to vinyl and vice versa, via GHC.Generics and generics-sop/records-sop.

Potential Use Cases

  • Reading an external data source (database query, results of API requests etc.) as a list of plain Haskell records and converting it to a list of vinyl records (for subsequent conversion to an in-memory data-frame).
  • Serializing a Frame/list of vinyl records to JSON.
  • Adding/removing fields from a plain record using vinyl as an intermediate representation.

Usage

Consider the following example module:

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE StandaloneDeriving    #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeOperators         #-}
module Example where

import           Data.Aeson
import           Data.Text
import           Data.Vinyl
import           Data.Vinyl.Generics.Transform (fromVinyl, toVinyl)
import qualified Generics.SOP                  as S
import qualified GHC.Generics                  as G

data MyPlainRecord = MPR {
  age      :: Int,
  iscool   :: Bool,
  yearbook :: Text
} deriving (Show, G.Generic)

instance S.Generic MyPlainRecord
instance S.HasDatatypeInfo MyPlainRecord

data MyType = 
  MyType { 
    bike :: Bool
  , skateboard :: Bool 
  } deriving (Show, G.Generic)

data MyPlainRecord2 = MPR2 {
  age      :: Int,
  iscool   :: Bool,
  yearbook :: Text,
  hobbies  :: MyType
} deriving (Show, G.Generic)

instance S.Generic MyPlainRecord2
instance S.HasDatatypeInfo MyPlainRecord2

In the above, let MyPlainRecord be the format in which data is being read from an external source. We also read some additional data additionalFields (say from a CSV using Frames):

-- some mock data
r1 :: MyPlainRecord
r1 = MPR { age = 23, iscool = True, yearbook = "!123!"}

additionalFields :: Rec ElField '[("age" ::: Int), ("hobbies" ::: MyType)]
additionalFields = xrec (23, MyType { bike = True, skateboard = True})

We'd like to add the field hobbies :: MyType to one such record ( :: MyPlainRecord), and want to have a record of type MyPlainRecord2. We can accomplish this by first isolating the field:

getHobbies :: Rec ElField '[("age" ::: Int), ("hobbies" ::: MyType)] 
             -> Rec ElField '[("hobbies" ::: MyType)]
getHobbies = rcast

...and then appending it to the vinyl representation of the plain record:

go :: MyPlainRecord2
go = fromVinyl $ (toVinyl r1) `rappend` (getHobbies additionalFields)

That's all there is to it. Once we have our vinyl record in plain record form, it is straightforward to serialize it to JSON:

instance ToJSON MyPlainRecord2
instance ToJSON MyType

Have a look at test/LibSpec.hs for more usage examples.

Known Limitations

This library, in its current form, works only with vinyl records with type-level field names (i.e. use the ElField interpretation functor). Future versions hope to tackle records with anonymous fields (e.g. heterogenous lists making use of the Identity functor) as well.