derive-topdown: Help Haskellers derive class instances for composited data types.

[ bsd3, development, library ] [ Propose Tags ]

This package will make it easier to derive class instance for complex composited data types by using Template Haskell.


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.0.0.1, 0.0.0.2, 0.0.0.7, 0.0.0.9, 0.0.1.0, 0.0.2.0, 0.0.2.1, 0.0.2.2, 0.0.3.0
Dependencies base (>=4.8 && <5.0), mtl (>=2.1.0), primitive (>=0.6.2), syb (>=0.4), template-haskell (>=2.10), th-expand-syns (>=0.4.3), transformers (>=0.4.2) [details]
License BSD-3-Clause
Copyright (C) songzh
Author songzh <Haskell.Zhang.Song@hotmail.com>
Maintainer songzh <Haskell.Zhang.Song@hotmail.com>
Category Development
Home page https://github.com/HaskellZhangSong/derive-topdown
Source repo head: git clone git://github.com/HaskellZhangSong/derive-topdown.git
Uploaded by songzh at 2017-10-11T12:17:47Z
Distributions LTSHaskell:0.0.3.0, NixOS:0.0.3.0, Stackage:0.0.3.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 4776 total (40 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2017-10-11 [all 1 reports]

Readme for derive-topdown-0.0.0.7

[back to package description]

derive-topdown

This is a Haskell project which will derive type class instances from top for a composite data type

standalone deriving

{-# LANGUAGE StandaloneDeriving,
	ConstraintKinds,      
	UndecidableInstances,
	-- You maybe need a lot of other extensions like FlexibleInstances and DerivingStrategies.
	DeriveGeneric
#-}
{-# OPTIONS_GHC -ddump-splices #-}

import Data.Derive.TopDown
import GHC.Generics
import Data.Binary
imoprt Data.Aeson
import Data.Aeson.TH

data Gender = Male | Female
type Age = Int
data Person a = P {name :: String , age :: Int, gender :: Gender}
data Department a = D {dname :: String , 
					   head :: Person a, 
					   staff :: [Person a]}
data Company a = C {cname :: String, 
                    departments :: [Department a]}

derivings [''Eq, ''Ord, ''Generic] ''Company

You will get:

	derivings [''Eq, ''Ord, ''Generic] ''Company
  ======>
    deriving instance Eq Gender
    deriving instance Eq (Person a_acKV)
    deriving instance Eq a_acKU => Eq (Department a_acKU)
    deriving instance Eq a_acKT => Eq (Company a_acKT)
    deriving instance Ord Gender
    deriving instance Ord (Person a_acKV)
    deriving instance Ord a_acKU => Ord (Department a_acKU)
    deriving instance Ord a_acKT => Ord (Company a_acKT)
    deriving instance Generic Gender
    deriving instance Generic (Person a_acKV)
    deriving instance Generic (Department a_acKU)
    deriving instance Generic (Company a_acKT)

For empty class instances deriving we can use it in this way. With DeriveAnyClasses and Generic class, we can use standalone deriving to do it. However, this is no reason to prevent you from doing this.

    instances [''Binary] ''Company
  ======>
    instance Binary Gender
    instance Binary (Person a_af50)
    instance Binary a_af4Z => Binary (Department a_af4Z)
    instance Binary a_af4Y => Binary (Company a_af4Y)

For generating instances with a template Haskell function, derivingTHs can be used:

   deriving_ths
      [(''ToJSON, deriveToJSON defaultOptions),
       (''FromJSON, deriveFromJSON defaultOptions)]
      ''Company
  ======>
    instance ToJSON Gender where
      toJSON
        = \ value_amQG
            -> case value_amQG of {
                 Male -> String (text-1.2.2.2:Data.Text.pack "Male")
                 Female -> String (text-1.2.2.2:Data.Text.pack "Female") }
      toEncoding
        = \ value_amQH
            -> case value_amQH of {
                 Male
                   -> Data.Aeson.Encoding.Internal.text
                        (text-1.2.2.2:Data.Text.pack "Male")
                 Female
                   -> Data.Aeson.Encoding.Internal.text
                        (text-1.2.2.2:Data.Text.pack "Female") }
    instance ToJSON a_amqg => ToJSON (Person a_amqg) where
      toJSON
        = \ value_amQy
        ...
        ...

You can use this function with derive(http://hackage.haskell.org/package/derive) package. It can handle more type classes, like Arbitrary in QuickCheck, especially.