Everybody loves a debate about changing some base
type classes, right?
The Alternative
class has four members right now: empty
and (<|>)
, of course, and some
and many
. The latter two have default implementations, and are presumably there so that they can be overridden (for performance?).
For many common types, though, those default implementations are entirely worthless. They very easily fall into infinite loops on non-trivial inputs. For example, some (Just 0)
ought to be Just [0,0..]
, but instead it loops forever:
some v = some_v
where
many_v = some_v <|> pure []
some_v = liftA2 (:) v many_v
some (Just 0)
= some_v
= liftA2 (:) (Just 0) many_v -- liftA2 is strict in last arg, so...
= liftA2 (:) (Just 0) (some_v <|> pure []) -- <|> is strict in first arg, so...
= liftA2 (:) (Just 0) ((liftA2 (:) (Just 0) many_v) <|> pure [])
-- ... and so on...
Similar thing happens with some [0..2]
(which ought to be repeat [0,0..]
) and some (
ZipList
[0..2])
(which ought to be ZipList [[0,0..],[1,1..],[2,2..]]
).
This is all mildly disappointing, but here’s something that would be pretty cool if it worked:
import Control.Applicative.Backwards
-- | Create an infinite list of infinite lists with elements
-- drawn from the input list. I am bad at naming functions.
--
-- >>> traverse_ print $ take 10 $ map (take 4) $ wezzle [0..2]
-- [0,0,0,0]
-- [1,0,0,0]
-- [2,0,0,0]
-- [0,1,0,0]
-- [1,1,0,0]
-- [2,1,0,0]
-- [0,2,0,0]
-- [1,2,0,0]
-- [2,2,0,0]
-- [0,0,1,0]
wezzle :: [a] -> [[a]]
wezzle = forwards . some . Backwards
This should work! The effect of Backwards
is to reverse the order of effects in a liftA2
, so under Backwards
instead of endlessly trying the first element forever, some
should iterate over the possibilities for the first element before moving on to the others. Neat stuff, except for the fact that it also fails in an infinite loop. Even with the effects of liftA2
reversed, the implementation of (<|>)
for lists is (++)
, which is strict in its first argument. So when we reduce many_v = some_v <|> pure []
, we go right back to reducing some_v
on an infinite ride.
But in a lazy language, we shouldn’t have this issue. We know that some_v <|> pure []
is going to be non-empty, because of that pure
on the right side! If only there was some way to make that fact known and defer the work of evaluating the head and tail, the liftA2
could proceed and start producing elements before looping back on itself.
Hold on to that thought.
Here’s another nifty function that actually does work:
-- | Create an infinite list of finite lists of every length,
-- with elements drawn from the input list. I am still bad at
-- naming functions.
--
-- >>> traverse_ print $ take 10 $ staggle [0,1]
-- []
-- [0]
-- [1]
-- [0,0]
-- [0,1]
-- [1,0]
-- [1,1]
-- [0,0,0]
-- [0,0,1]
-- [0,1,0]
staggle :: [a] -> [[a]]
staggle = greedy . forwards . many . Backwards . Lazy
newtype Lazy f a = Lazy { greedy :: f a }
deriving (Functor, Applicative)
instance Alternative f => Alternative (Lazy f) where
empty = Lazy empty
Lazy l <|> Lazy r = Lazy $ r <|> l
Lazy
, like its cousins Backwards
and Dual
and Reverse
, is a newtype that exists only to flip an underlying operation. (Since the prevailing convention with Alternative
is to put the greedier operation to the left of (<|>)
, flipping (<|>)
turns greedy parsers into lazy parsers. But of course, not everything Alternative
is actually a parser.) We get finite lists instead of infinite lists because we’re trying shorter options first now.
I bring this function up to make a point about (<|>)
. One possible way to resolve the infinite loop problem with wezzle
would be to change the Alternative []
instance’s implementation of (<|>)
to something lazy in its first argument (and strict in its second, where we know the pure []
will be). However, if we did that, we’d break staggle
, and that’s unacceptable! Ideally the smooth operation of some
and many
would not rely on assuming which of the arguments of (<|>)
is strict. But implementing list concatenation with two non-strict arguments isn’t possible, so something else needs to change.
Control.Applicative
also contains a function optional
, which conceptually seems cut from the same cloth as some
and many
. Here is its implementation:
optional :: Alternative f => f a -> f (Maybe a)
optional v = Just <$> v <|> pure Nothing
Reminds you a bit of the definition of many_v
, doesn’t it? We can reimplement many_v
in the definitions of some
and many
using optional
, like this:
many_v = fromMaybe [] <$> optional some_v
This by itself doesn’t solve our problem. But if optional
were promoted to be a fifth member of Alternative
(finally arriving at the title of this post!), then we could give it a non-default implementation that is fully lazy in its one argument, for the types that have been causing problems!
(Click to see the full proposed definition of Alternative
)
class Applicative f => Alternative f where
empty :: f a
(<|>) :: f a -> f a -> f a
some :: f a -> f [a]
some v = some_v
where
many_v = fromMaybe [] <$> optional some_v
some_v = liftA2 (:) v many_v
many :: f a -> f [a]
many v = many_v
where
many_v = fromMaybe [] <$> optional some_v
some_v = liftA2 (:) v many_v
-- new!
optional :: f a -> f (Maybe a)
optional v = Just <$> v <|> pure Nothing
Let’s see how this fixes the various problems I’ve brought up:
instance Alternative Maybe where
empty = Nothing
Nothing <|> r = r
l <|> _ = l
-- new!
optional = Just
This time, evaluating some (Just 0)
goes like this:
some v = some_v
where
many_v = fromMaybe [] <$> optional some_v
some_v = liftA2 (:) v many_v
some (Just 0)
= some_v
= liftA2 (:) (Just 0) many_v -- liftA2 is strict in last arg, so...
= liftA2 (:) (Just 0) (fromMaybe [] <$> optional some_v) -- <$> is strict in second arg, so...
= liftA2 (:) (Just 0) (fromMaybe [] <$> Just some_v)
= liftA2 (:) (Just 0) (Just (fromMaybe [] some_v))
= Just (0 : (fromMaybe [] some_v))
And there we are in WHNF! Forcing the evaluation deeper produces Just [0,0..]
as desired.
I won’t walk through the evaluations for some [0..2]
and some (ZipList [0..2])
, but here are the implementations that allow them to be productive:
instance Alternative [] where
empty = []
(<|>) = (++)
-- new!
optional xs = let
(h, t) = case xs of
x : xs' -> (Just x, optional xs')
[] -> (Nothing, [])
in h : t
instance Alternative ZipList where
empty = ZipList []
ZipList xs0 <|> ZipList ys0 = ZipList $ go xs0 ys0
where
go (x:xs) (_:ys) = x : go xs ys
go [] ys = ys
-- new!
optional (ZipList xs) = let
(h, ZipList t) = case xs of
x : xs' -> (Just x, optional $ ZipList xs')
[] -> (Nothing, pure Nothing)
in ZipList $ h : t
Finally, to make wezzle
work, the Alternative (Backwards f)
instance needs to use the optional
implementation from f
instead of its own default:
instance Alternative f => Alternative (Backwards f) where
empty = Backwards empty
Backwards x <|> Backwards y = Backwards $ x <|> y
optional (Backwards x) = Backwards $ optional x
This doesn’t interfere with the correct operation of staggle
, happily! And since optional
only uses pure
from Applicative
, we don’t have to worry about circumventing the intended effect of Backwards
, which is all about reversing (<*>)
and liftA2
and such.
If you’ve read this far, thank you for paying this much attention to a pretty unsexy proposal. Here is a working online copy of all of the code in this post.
I think this makes a decent case for promoting optional
to a proper class member in Alternative
, and illustrates some neat tricks that could be possible using some
and many
outside of the context of parsers. On the other hand, the CLC seems generally to want a very strong case for adding members to existing classes (per this comment, for example), and so: is this compelling to anyone other than me and my mostly academic use cases? And are there any issues with this proposal that I haven’t seen?