matchable-th: Generates Matchable instances using TemplateHaskell

[ bsd3, functors, library ] [ Propose Tags ]

This package provides TemplateHaskell function to generate instances of Matchable and Bimatchable type classes, which are from "matchable" package.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.1.2.0, 0.1.2.1, 0.2
Change log CHANGELOG.md
Dependencies base (>=4.9 && <5), matchable (>=0.1.2), template-haskell (>=2.4 && <2.15), th-abstraction (<0.3) [details]
License BSD-3-Clause
Author Koji Miyazato
Maintainer viercc@gmail.com
Revised Revision 1 made by phadej at 2019-05-03T17:58:38Z
Category Functors
Source repo head: git clone https://github.com/viercc/matchable -b master
Uploaded by viercc at 2019-01-07T09:35:43Z
Distributions NixOS:0.2
Downloads 1121 total (20 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-01-07 [all 1 reports]

Readme for matchable-th-0.1.0.0

[back to package description]

matchable-th

This package provides TemplateHaskell functions to generate instances of Matchable and Bimatchable type classes, which are from matchable package.

Example

{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TemplateHaskell #-}

import Data.Functor.Classes (Eq1(..))
import Data.Matchable
import Data.Matchable.TH

newtype G a = G [(a, Int, a)]
  deriving (Show, Eq, Functor)

$(deriveMatchable ''G)

-- @deriveMatchable@ generates a @Matchable@ instance only,
-- so you also have to declare @Functor G@ and @Eq1 G@.
-- There is a handy @DeriveFunctor@ extension.
-- Also, you can use @liftEqDefault@ to easily implement @liftEq@.
instance Eq1 G where
  liftEq = liftEqDefault
{-# LANGUAGE TemplateHaskell #-}

import Data.Functor.Classes (Eq2(..))
import Data.Bimatchable
import Data.Matchable.TH

data BiG a b = BiG0 | BiG1 [a] [b] | BiG2 (Int, BiF a b)

instance Eq2 BiG where
  liftEq2 = liftEq2Default

instance Bifunctor BiG where
  bimap = bimapRecovered

$(deriveBimatchable ''BiG)