I’ve been trying for a while to write a Haskell library for set/semigroup/monoid/group actions (I know some already exist). One design I’ve been wanting to use is to define the class
class LAct s x where
lact :: s -> x -> x
infixr 5 `lact`
and then add different properties this action might satisfy like the following ones :
-- (s <> t) <>$ x === s <>$ t <>$ x
class (LAct s x, Semigroup s) => LActSg s x
-- mempty <>$ x === x
class (LActSg s x, Monoid s) => LActMn s x
-- s <>$ (x <> y) === (s <>$ x) <> (s <>$ y)
class (LActSg s x, Semigroup x) => LActSgMorph s x
-- s <>$ mempty === mempty
class (LActMn s x, LActSgMorph s x, Monoid x) => LActMnMorph s x
Now in terms of instances, I would like to be able to write both instances of the form
-- driven by second parameter
instance LAct s x => LAct s [x] where
lact s l = map (s <>$) l
-- driven by first parameter
instance LAct s x => LAct [s] x where
lact l x = foldr lact x l
Now this absolutely cannot work and will always overlap. Worse, no instance would be a specialisation of the other one.
There is a trick though. It looks pretty nasty but it does work : I can decide that instances of LAct
are always driven by the first parameter, and declare another type class LAct’ that is driven by the second parameter along with a lifting of all instances of LAct’ into instances of LAct
class LAct' s x where
lact' :: s -> x -> x
instance {-# OVERLAPPABLE #-} LAct' s x => LAct s x where
(<>$) = lact'
Now I wan define the following instance that will always be chosen by the type checker only if it doesn’t find any first driven parameter instance
instance LAct s x => LAct' s [x] where
lact' s l = map (s <>$) l
This is more comfortable to code with as it seems, and one do not have to bother about overlapping instances, just use LAct’ when one need an instance driven by the second parameter.
But there is a huge problem when I start to combine this trick with action properties like LActSg, LActMn…
I could declare second paramater driven versions of this properties, by writing something like
class (LAct' s x, Semigroup s) => LActSg' s x
instance LActSg [s] x where
lact l x = foldr lact x l
instance {-# OVERLAPPABLE #-}LActSg' s x => LActSg s x
But this is wrong because of the overlappings. There might be cases where the instance above is not opverlapped (because the overlapping action does NOT have the semigroup action property) but the type system will still think that this action has the property.
So here is my questions :
- How common is the practice of using type classes as some mathematical properties ?
(There are some packages like commutative-semigroups that relies only on this trick) - Is it considered good practice ?
- It feels fundamentally not compatible with overlapping instances, how bad is it ? Is this something you’ve already experienced ?
I’d like to finish this post with an idea. One way to solve some of those questions would be to have some kind of Haskell extension that I would call something like “ExplicitLaws”
It would allow to write something like the following
{-# LANGUAGE ExplicitLaws #-}
class LAct s x where
law LActSg s x
law LActMn s x
law LActSgMorph s x
law LActMnMorph s x
implies LActMn s x => LActSg s x
implies LActSgMorph s x => LActSg s x
implies LActMnMorph s x => (LActSg s x, LActSgMorph s x)
(<>$) :: s -> x -> x
instance LAct s x => LAct [s] x where
abides LActMn s x
lact l x = foldr lact x l
-- We could use such explicit laws in a lot of cases, for instance for defining Semigroup in terms of Magma
class Magma s where
law Associative s
law Commutative s
(<>) :: s -> s -> s
type Semigroup s = (Associative s, Magma s)
instance Semigroup (Sum Int) where
-- somehow the compiler adds the "abides" declaration itself since it is an instance of Semigroup
(<>) = (+)