[Haskell-cafe] List instance of Alternative: why (++)?

Clinton Mead clintonmead at gmail.com
Mon May 8 05:57:41 UTC 2017


Where mappend, mplus and <|> and <> are defined, do they (and should they)
always produce the same results?

On Sun, May 7, 2017 at 5:23 PM, Jon Purdy <evincarofautumn at gmail.com> wrote:

> D’oh, that’s what I get for writing untested code in an email.
>
> Neutral doesn’t seem necessary since we have “null” in Foldable. I was
> thinking more along these lines:
>
> instance (Alternative f, Foldable f) => Alternative (LeftBiased f) where
>   empty = LeftBiased empty
>   LeftBiased a <|> LeftBiased b = LeftBiased (if null a then b else a)
>
> Under the assumption that “null empty” always holds. I think using the
> Alternative constraint for just “empty” makes sense because LeftBiased and
> RightBiased should only differ from the wrapped type in the implementation
> of (<|>), but it still seems a little iffy somehow.
>
> To make the wrapping slightly less painful, another good bikeshed colour
> would be Pre/Post. (Dunno what you’d call “Unbiased” in that case, though.)
>
> On a related note, I recall there was some discussion a while back about
> making a Monoid instance for Map where mappend is “unionWith mappend”
> instead of the left-biased “union”. These wrappers could also be used for
> that sort of thing, and it’d be nice to have a single standard for them
> with all the different use cases fleshed out.
>
> On Sat, May 6, 2017 at 4:19 PM, MarLinn <monkleyon at gmail.com> wrote:
>
>>
>> On 2017-05-07 00:23, Jon Purdy wrote:
>>
>> I’ve wanted this before as well. Maybe we should throw a newtype at it?
>>
>> newtype LeftBiased a = LeftBiased [a]
>> instance Alternative (LeftBiased a) where
>>   empty = []
>>   [] <|> b = b
>>   a <|> _ = a
>>
>> newtype RightBiased a = RightBiased [a]
>> instance Alternative (RightBiased a) where
>>   empty = []
>>   a <|> [] = a
>>   _ <|> b = b
>>
>> You forgot the fun wrapping and unwrapping. But no matter. Let's
>> generalize!
>>
>> 	class Neutral a where
>> 	    neutral :: a
>> 	    isNeutral :: a -> Bool
>>
>> 	instance Neutral a => Alternative (LeftBiased  a) where
>> 	    empty = LeftBiased neutral
>> 	    (LeftBiased  a) <|> (LeftBiased  b) = LeftBiased  $ if isNeutral a then b else a
>>
>> 	instance Neutral a => Alternative (RightBiased a) where
>> 	    empty = RightBiased neutral
>> 	    (RightBiased a) <|> (RightBiased b) = RightBiased $ if isNeutral b then a else b
>>
>> Why?
>>
>> 	type AllRight e a = LeftBiased  (Either e a)
>> 	type AnyRight e a = RightBiased (Either e a)
>>
>> 	instance Neutral a => Neutral (AllRight e a) where
>> 	    neutral = Right $ LeftBiased  neutral
>> 	    isNeutral = fmap isRight
>>
>> 	instance Neutral e => Neutral (AnyRight e a) where
>> 	    neutral = Left  $ RightBiased neutral
>> 	    isNeutral = fmap isLeft
>>
>> Is this a bit silly? Yes. My actual goal is to show that these concepts
>> are bigger than they might appear, and how painful all those wrappers are.
>> This is to advertise my language extension from my separate thread. And
>> also because it's silly fun. Mostly that.
>>
>>
>> newtype Unbiased a = Unbiased (Maybe a)
>> instance (Monoid m) => Alternative (Unbiased m) where
>>   empty = Nothing
>>   Just a <|> Just b = Just (a <> b)
>>   _ <|> Just b = Just b
>>   Just a <|> _ = Just a
>>   _ <|> _ = Nothing
>>
>> Mh, that's just liftA2 (<>) a b <|> a <|> b in terms of the regular
>> instance. Now that is easy to generalize – just don't use it for lists.
>> Cheers,
>> MarLinn
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170508/1ecd2ad7/attachment.html>


More information about the Haskell-Cafe mailing list