3

Is there a package that does roughly the following:

Given a record:

data R = R { a :: TypeA,
             b :: TypeB,
             c :: TypeC }

derives a lifted record:

data R_L f = R_L { a_L :: f TypeA,
                   b_L :: f TypeB,
                   c_L :: f TypeC }

and offers a couple of instances and functions similar to:

instance (Monoid (f TypeA), Monoid (f TypeB), Monoid (f TypeC))
         => (Monoid (R_L f)) where
  mempty = R_L mempty mempty mempty
  mplus a b = ...fieldwise mplus...

sequenceR :: (Monad m) => R_L m -> m R
sequenceR = ... run fields, sum results ...
sequenceRA :: (Applicative m) => R_L m -> m R
sequenceRA x = R <$> a_L x <*> b_L x <*> c_L x

and probably others. Is there a package that provides this functionality and when not, which of the mechanisms (TH? Generics?) is best to use to implement it?

Gracjan Polak
  • 596
  • 3
  • 16

2 Answers2

4

The monoid part is possible with generic-deriving, which offers an alternative GMonoid, of which generics are automatically an instance.

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances, FlexibleContexts, DefaultSignatures #-}

import Data.Monoid
import qualified Generics.Deriving.Monoid as M

data R_L f = R_L { a :: f [()],
                   b :: f String,
                   c :: f () } deriving (Generic)

Now you can do the following:

*Main> let x = R_L (Just [()]) Nothing (Just ()) `M.gmappenddefault` R_L (Just [()]) (Just "foo") (Just ())
*Main> a x
Just [(),()]
*Main> b x
Just "foo"
*Main> c x
Just ()

(I am still figuring out the generic Show instance.)

An ordinary Monoid instance can be created as follows (thought, that might be called boilerplate again...):

instance (Monoid (f [()]), Monoid (f String), Monoid (f ())) => Monoid (R_L f) where
    mempty = M.memptydefault
    mappend = M.mappenddefault

In the package, there are also other derived instances for Functor, Traversable and Foldable.

Monad and Applicative can maybe be modelled with generics similar to the existing instances, if you change the kind of your type; although, maybe not in the way you like, since, I think, they would only make sense as a product functor of the fields' types, and not as you propose.

phipsgabler
  • 20,535
  • 4
  • 40
  • 60
  • 1
    Thanks for generic-deriving hint, that should be useful. Note though that your suggestion does not derive R_L from R so it is a partial solution for me. – Gracjan Polak Jul 15 '14 at 20:01
  • Oh, I'm sorry, I misinterpreted/overread your use of _deriving_. I'll still leave the answer, sincy you have found it helpful. – phipsgabler Jul 16 '14 at 10:25
0

In the true open source spirit I wrote my own library:

http://hackage.haskell.org/package/fieldwise

https://github.com/gracjan/fieldwise

Gracjan Polak
  • 596
  • 3
  • 16