Hi all,

I'd like to announce a hopefully useful new package: algebraic-classes. In 
short it provides conversions between algebraic classes and F-algebras, which 
should make generating instances of certain classes easier.

Algebraic classes are classes where every method has the same result type, 
which is the class parameter. Examples are Num and Monoid. F-algebras are 
functions of the form f a -> a, with f a functor, which can be called the 
signature of the algebra. They are equivalent as follows: Algebraic classes are 
signatures, and the instances of algebraic classes are specific algebras. Take 
for example the Monoid class:

  class Monoid a where
    mempty :: a
    mappend :: a -> a -> a

The equivalent signature would be:

  data MonoidSignature a = Op_mempty | Op_mappend a a

And the list instance 

  instance Monoid [a] where
    mempty = []
    mappend = (++)

would be equivalent to the algebra:

  listAlgebra :: MonoidSignature [a] -> [a]
  listAlgebra Op_mempty = []
  listAlgebra (Op_mappend a b) = a ++ b

And there is an obvious monoid algebra for any Monoid instance:

  evaluate :: Monoid a => MonoidSignature a -> a
  evaluate Op_mempty = mempty
  evaluate (Op_mappend a b) = mappend a b

Using Template Haskell, the algebraic-classes library can generate signatures 
and evaluation functions from algebraic classes, and class instances from 
algebras. Also, for the signatures Functor and Traversable are derived using 
the DeriveFunctor and DeriveTraversable. That makes it possible to create 
algebras generically for any signature in certain cases, which together with 
the conversions means you can generate instances generically.

Take tuples for example: if given that both components are instances of a 
class, then we can create the algebra as follows:

algebra :: (Functor f, Class f m, Class f n) => f (m, n) -> (m, n)
algebra fmn = (evaluate (fmap fst fmn), evaluate (fmap snd fmn))

And for any applicative functor we can do the same:

algebra :: (Traversable f, Applicative g, Class f a) => f (g a) -> g a
algebra = fmap evaluate . sequenceA

Taken all together, all you have to do to get for example the Monoid instance 
for Either a b (based on its applicative instance) is:

deriveInstance [t| Monoid b => Monoid (Either a b) |]

The package lives on Hackage here:

http://hackage.haskell.org/package/algebraic-classes

And if you have suggestions, issues (the Template Haskell code is far from 
perfect at the moment) or pull-request, it is also on Github:

https://github.com/sjoerdvisscher/algebraic-classes

greetings,
Sjoerd Visscher


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to