[Haskell-cafe] Textbook example of instance Foldable ((,)a)

Viktor Dukhovni ietf-dane at dukhovni.org
Thu Nov 26 20:20:22 UTC 2020


On Wed, Nov 25, 2020 at 11:24:41PM -0500, Viktor Dukhovni wrote:

> > It's not hard to imagine, in the absence of these instances, Haskell
> > loosening the restriction on creating these types of instances. The
> > restriction is certainly not innate to mathematics or type theory.
> 
> Type inference would get more complicated if it would have to consider
> all possible slots in each term when searching for the instance head.
> 
> > My position is against having most of these instances in base, not for
> > switching the bias from right to left.
> 
> So you'd like to see a 2-tuple with fewer built-in instances, I'm
> sympathetic to the case for not having Traversable/Foldable for
> 2-tuples, but I don't see a compelling for not having Functor/Monad.

Would the attached module be useful to you or anyone else?  It
implements two newtype-wrapped types: 'LP a b' and 'RP a b'.

'LP a b' has a run-time represenation of (and is coercible to) (b, a).
It is a Functor, Applicative and Monad in the left slot of the
underlying 2-tuple.

'RP a b' has a run-time representation of (a, b) and is a Functor,
Applicative and Monad in the right slot of the underlying 2-tuple.

    λ> :t LP (1, "foo")
    LP (1, "foo") :: Num b => OrderedPair 'BL [Char] b
    λ> :t RP (1, "foo")
    RP (1, "foo") :: Num a => OrderedPair 'BR a [Char]

These share the "safe" class instances of (,) from Prelude, but omit
the potentially problematic Foldable (and hence also Traversable).

    λ> fmap succ $ LP (1, 10)
    LP (2,10)
    λ> fmap succ $ RP (1, 10)
    RP (1,11)

The Bifunctor instance is therefore "flipped" in the "LP" case:

    λ> bimap succ pred $ LP (1, 10)
    LP (0,11)
    λ> bimap succ pred $ RP (1, 10)
    RP (2,9)

The class 'LROrder' exports zero-cost coercions to ordinary 2-tuples,
and also conversions to 2-tuples that take/return (a, b) regardless
of the underlying 2-tuple representation.

    λ> toPair $ LP (1, "foo")
    (1,"foo")
    λ> rePair $ LP (1, "foo")
    ("foo",1)
    λ> toPair $ RP (1, "foo")
    (1,"foo")
    λ> rePair $ RP (1, "foo")
    (1,"foo")

Application code can be polymorphic in the 2-tuple order:

    foo :: LROrder o => ((a, b) -> x) -> OrderedPair o a b -> x
    foo f = f . rePair

    bar :: LROrder o => (b -> c) -> OrderedPair o a b -> OrderedPair o a c
    bar f = fmap f

or when desired work with a given order using coercions to extract the
underlying representation for interaction with external libraries.

    foo :: ((b, a) -> x) -> LP a b -> x
    foo f = f . toPair

    bar :: ((a, b) -> x) -> RP a b -> x
    bar f = f . toPair

    baz :: (b -> c) -> ((c, a) -> x) -> LP a b -> x
    baz f g = g . toPair . fmap f

I expect that for most cases the (b, a) representation is not
particularly compelling.  And the order-polymorphism is not needed.  In
other words, the existing "bias" of Functor, Applicative and Monad to
operate on the second element is a natural convention rather than an
obstacle.

-- 
    Viktor.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: LRPair.hs
Type: text/x-haskell
Size: 3742 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20201126/c76eda7f/attachment.hs>


More information about the Haskell-Cafe mailing list