[Haskell-cafe] Textbook example of instance Foldable ((,)a)
Viktor Dukhovni
ietf-dane at dukhovni.org
Wed Nov 25 23:13:10 UTC 2020
On Wed, Nov 25, 2020 at 04:15:18PM -0500, amindfv--- via Haskell-Cafe wrote:
> > The "symmetry breaking" is not a result of the perhaps regrettable
> > Foldable instance, rather it is a basic consequence of the fact that
> > given:
> >
> > data Foo a b = Foo a b
> >
> > we immediately get a Functor "Foo a :: * -> *" for each a, of which
> > "(,) a" is but one example. I find nothing objectionable in the Functor
> > instance "(,) a" or the Bifunctor instance "(,)". It is only the
> > Traversable and Foldable instances of "(,) a" that have the noted
> > unexpected behaviour.
>
> This is almost incidental, though, right? I.e. it's just a result of
> typeclass "currying" syntax,
Yes, the last type variable gets the "for free" functor instance.
> but it's not hard to imagine a Haskell where [...]
>
> we're also allowed to write something like:
>
> instance Functor (\a -> Foo a b)
> instance Functor (\a -> (a, b))
>
> Mirroring the current (implicit)
>
> instance Functor (\b -> Foo a b)
> instance Functor (\b -> (a, b))
>
> If that were the case, the instances favoring the last paramater
> wouldn't seem natural at all, and we'd be sensibly asking on what
> basis "(+1) <$> (2, 4)" equals (2, 5) but not (3, 4).
The intent is clear, but ultimately not as useful as one might wish,
since when it comes down to evaluating terms:
fmap f (x, y)
at most one such instance can match, since the terms don't carry any
information about whether you want to fmap on the left or right. So
all you'd get to do is flip the bias from right to left.
To avoid the bias we have Bifunctors:
first :: Bifunctor p => (a -> b) -> p a c -> p b c
second :: Bifunctor p => (b -> c) -> p a b -> p a c
For selectable bias on 2-tuples, one needs newtypes:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
import Data.Bifunctor
import Data.Coerce
class Coercible c (a,b) => NewPair c a b | c -> a, c -> b where
toPair :: c -> (a, b)
toPair = coerce
{-# INLINE toPair #-}
fromPair :: (a, b) -> c
fromPair = coerce
{-# INLINE fromPair #-}
-- RPair is redundant, except to avoid Foldable, ... instances
newtype LPair b a = LPair (a, b) deriving (Eq, Ord, Read, Show)
newtype RPair a b = RPair (a, b) deriving (Eq, Ord, Read, Show)
instance NewPair (a, b) a b
instance NewPair (LPair b a) a b
instance NewPair (RPair a b) a b
instance Functor (LPair a) where
fmap f = fromPair . first f . toPair
instance Functor (RPair a) where
fmap f = fromPair . second f . toPair
with the above:
λ> fmap succ $ LPair (1, 10)
LPair (2,10)
λ> fmap succ $ RPair (1, 10)
RPair (1,11)
--
Viktor.
More information about the Haskell-Cafe
mailing list