relaxing instance declarations
Ben Millwood
haskell at benmachine.co.uk
Thu May 2 13:19:42 CEST 2013
On Tue, Apr 30, 2013 at 09:46:01PM -0400, Edward Kmett wrote:
>instance Foldable Baz where
> foldmap f (Baz a) = f a
>
>is an innocent typo that would then just mean that foldMap when applied to
>Baz will silently loop forever with no warning to the programmer.
>Traversable Baz behaves similarly with the cyclic between sequenceA+fmap
>and traverse.
Maybe we need a better answer for the default method cycle problem? I
had the following vague idea one day: don't allow default definitions in
class members. Just use things along the lines of fmapDefault, or, say,
subtractFromPlusNegate :: (n -> n -> n) -> (n -> n) -> n -> n -> n
subtractFromPlusNegate (+!) neg a b = a +! neg b
A bit clumsier but way more explicit: no more warning-silent infinite
loops from code you didn't even write. The only drawback is the lack of
the ability to introduce new class methods with default definitions.
But! Here's my second idea: use RecordWildcards and NamedFieldPuns,
allow pattern bindings instead of just simple variables in class
instances, and do something like this:
data MonoidInstance m = MkMonInst
{ mempty :: m
, mappend :: m -> m -> m
}
monoidFromMconcat :: ([m] -> m) -> MonoidInstance m
monoidFromMconcat mcat = MkMonInst
{ mconcat = mcat
, mempty = mcat []
, mappend x y = mcat [x,y]
}
-- possibly slightly silly
monoidFromMemptyMappend :: m -> (m -> m -> m) -> MonoidInstance m
monoidFromMemptyMappend mempty mappend = MkMonInst {..}
where
mconcat = foldr mempty mappend
instance Monoid [a] where
MkMonInst {..} = monoidFromMconcat concat
Now if I later wanted to add a new method to Monoid, I could just add a
new field to MonoidInstance and have the instance-generator functions
produce it from the others.
Notice that this also leaves me free to have overlapping minimal
complete definitions, which the current system doesn't – I explicitly
state which one I am using by my choice of monoidFrom function.
Anyway, that's something of a digression. My opinion on the issue at
hand is that I'd very much like to see a general form of
"declaration-let" that would allow me to declare some things local to a
group of bindings. If I understand correctly, this would make the
specific proposal at hand redundant, and is useful in other situations
as well.
-- Ben
More information about the Haskell-prime
mailing list