mgeneric: Generics with multiple parameters

[ data, library, mit ] [ Propose Tags ]

This package provides an implementation of generics with multiple parameters in Haskell, as described in http://dreixel.net/research/pdf/gpmp_colour.pdf.

A MGeneric instance can be derived for most datatypes with deriveMGeneric ''Type

It also provides the type classes MFunctor, MFoldable and MTraversable, generalisations of Functor, Foldable and Traversable to kinds other than (* -> *), and the type class MZipWith.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0.0.0, 0.0.0.1, 0.0.0.2
Dependencies base (>=4.5 && <5), containers, lens, mtl, template-haskell [details]
License MIT
Author Rafaël Bocquet
Maintainer Rafaël Bocquet <rafaelbocquet+github@gmail.com>
Category Data
Home page http://github.com/RafaelBocquet/haskell-mgeneric/
Bug tracker http://github.com/RafaelBocquet/haskell-mgeneric/issues
Source repo head: git clone git://github.com/RafaelBocquet/haskell-mgeneric.git
Uploaded by rbocquet at 2015-03-21T13:39:44Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2235 total (10 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-03-21 [all 1 reports]

Readme for mgeneric-0.0.0.2

[back to package description]

MGeneric : Generics with Multiple parameters

https://hackage.haskell.org/package/mgeneric

This package provides an implementation of generics with multiple parameters in Haskell, as described in http://dreixel.net/research/pdf/gpmp_colour.pdf.

A MGeneric instance can be derived for most datatypes with deriveMGeneric ''Type

It also provides the type classes MFunctor, MFoldable and MTraversable, generalisations of Functor, Foldable and Traversable to kinds other than (* -> *), and the type class MZipWith.

Examples

MFunctor

kind Variance = CoV | ContraV
-- f is the functor
-- (fs :: [*]) are the mapping functions
-- (vs :: [Variance]) are the variances of f
mmap :: MFunctor f fs vs => HList fs -> f :$: Domains fs vs -> f :$: Codomains fs vs
data Test a b = Test [a -> b]
deriveMGeneric ''Test
instance Unapply (Test a b) Test '[a, b]
instance MFunctor Test '[a' -> a, b -> b'] '[ContraV, CoV]

test :: Test Int String -> Int -> [String]
test (Test a) i = fmap ($ i) a

a :: Test Int String
a = Test [show, const "A"]

b :: Test Int String
b = mmap (HCons (+ 1) (HCons ("TEST " ++) HNil)) a
ghci> test b 41
["TEST 42", "TEST A"]

MFoldable

-- MonoidMap as m ~ Map (\a -> (a -> m)) as
mfoldMap :: (Monoid m, MFoldable f as) => HList (MonoidMap as m) -> f :$: as -> m
data Test a b c = Test ([a, [b]], c) deriving (Show)
deriveMGeneric ''Test
instance Unapply (Test a b c) Test '[a, b, c]
instance MFoldable Test '[a, b, c]


a :: Test Int String Char
a = Test ([(0, [""]), (1, ["a", "b"]), (3, ["foo", "bar"])], 'e')
ghci> mfoldMap (const mempty `HCons` (Sum . length) `HCons` (Sum . ord) `HCons` HNil) a
Sum 109

MTraversable

-- AppMap fs t ~ Map (\(a -> b) -> (a -> t b)) as
mtraverse :: (MTraversable f fs t) => HList (AppMap fs t) -> f :$: Domains fs -> t (f :$: Codomains fs)
-- SequenceMap as t ~ Map (\(a -> b) -> (t a -> t b)) as
msequence :: (MTraversable f (SequenceMap as t) t) => f :$: Map as t -> t (f :$: as)
data Test a b c = Test ([(a, [b])], c) deriving (Show)
deriveMGeneric ''Test
instance Unapply (Test a b c) Test '[a, b, c]
instance MTraversable Test '[a -> a', b -> b', c -> c']


a :: Test Int String Char
a = Test ([(0, [""]), (1, ["a", "b"]), (3, ["foo", "bar"])], 'e')
ghci> evalState ?? "A"
       $ mtraverse ((\i -> do { s' <- get; put (show i); return (length s') })
            `HCons` (\s -> do { s' <- get; put s; return s' })
            `HCons` pure `HCons` HNil) a
Test ([(1,["0"]),(0,["1","a"]),(1,["3","foo"])],'e')

MZipWith

mzipWith zips n structures together if they have the same shape, or fails (with Nothing) if the shapes do not match.

-- ZipWithType NZ     f fs ~ Maybe (f :$: fs)
-- ZipWithType (NS n) f fs ~ f :$: Domains fs -> ZipWithType n f (Codomains fs)
mzipWith :: MZipWith n f fs => HList fs -> ZipWithType n f fs
-- mzipWith n :: HList (a1 -> a2 -> ... -> an, ...) -> f a1 b1 ... -> f a2 b2 ... -> ... -> Maybe (f an bn ...)
data Test a b c = Test ([(a, [b])], c) deriving (Show)
deriveMGeneric ''Test
instance Unapply (Test a b c) Test '[a, b, c]
instance ( MZipWithG n Test (Rep (Test :$: LCodoms n '[f, g, h])) '[f, g, h]
         , GMZipWith n (Rep (Test :$: LCodoms n '[f, g, h])) '[f, g, h]
         ) => MZipWith n Test '[f, g, h]


a :: Test Int String Char
a = Test ([(0, [""]), (1, ["a", "b"]), (3, ["foo", "bar"])], 'e')

b :: Test Int String Char
b = Test ([(1,["0"]),(0,["1","a"]),(1,["3","foo"])],'h')

c :: Maybe (Test Int String Int)
c = mzipWith ((\a b -> Just (a + b)) `HCons` (\a b -> Just (a ++ b)) `HCons` (\a b -> Just 0) `HCons` HNil) a b
ghci> c
Just (Test ([(1,["0"]),(1,["a1","ba"]),(4,["foo3","barfoo"])],0))

TODO

  • Add more generic type classes
  • Add inline annotations
  • Add documentation
  • Handle FK in ZipWith ?
  • Reduce the need for Proxy types
  • Find more suitable names for type level functions
  • Handle all cases in deriveMGeneric, and provide more relevant error messages
  • Drop the dependency on lens