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