Proposal: add unfoldr1 to the somewhere in base

Way back in 2001, Shin-Cheng Mu proposed an unfoldr1 combinator: http://code.haskell.org/~dons/haskell-1990-2000/msg06775.html I discussed this a bit with shachaf in #haskell, and he noted that a similar function, with a slightly different but isomorphic type, appears in Edward Kmett's semigroups package as the unfoldr for NonEmpty. I propose that we add this. It can be written unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f b = go b where go b = case f b of (a, may_b) -> a : maybe [] go may_b With the appropriate RULES, it can be wrapped up in build and fuse properly. I'd love to see this written as an unfoldr instead. Does anyone know if that's possible?

I forgot to mention why I even want this. Specifically, I'm trying to
see to what extent we can strip the single-purpose RULES and manual
unboxing out of GHC.Enum by fixing unfoldr and adding any other
necessary general-purpose functions. We can do this for enumFromTo
with just unfoldr:
{-# INLINE eft #-}
eft :: Enum n => n -> n -> [n]
eft m n = efatGenInt (fromEnum m) (fromEnum n) ++ [n] -- Magic: that
++ [n] is transformed away.
{-# INLINE efatGenInt #-}
efatGenInt :: Enum n => Int -> Int -> [n]
efatGenInt m n = if m > n then [] else map toEnum $ unfoldr go m
where
go x | x == n = Nothing
| otherwise = Just (x, x+1)
But when we get to the more complex enumFromThenTo, things seem to get
very messy unless we can use unfoldr1.
On Fri, Aug 1, 2014 at 7:21 PM, David Feuer
Way back in 2001, Shin-Cheng Mu proposed an unfoldr1 combinator: http://code.haskell.org/~dons/haskell-1990-2000/msg06775.html
I discussed this a bit with shachaf in #haskell, and he noted that a similar function, with a slightly different but isomorphic type, appears in Edward Kmett's semigroups package as the unfoldr for NonEmpty.
I propose that we add this. It can be written
unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f b = go b where go b = case f b of (a, may_b) -> a : maybe [] go may_b
With the appropriate RULES, it can be wrapped up in build and fuse properly.
I'd love to see this written as an unfoldr instead. Does anyone know if that's possible?

On Fri, Aug 1, 2014 at 7:21 PM, David Feuer
Way back in 2001, Shin-Cheng Mu proposed an unfoldr1 combinator: http://code.haskell.org/~dons/haskell-1990-2000/msg06775.html
I discussed this a bit with shachaf in #haskell, and he noted that a similar function, with a slightly different but isomorphic type, appears in Edward Kmett's semigroups package as the unfoldr for NonEmpty.
I propose that we add this. It can be written
unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f b = go b where go b = case f b of (a, may_b) -> a : maybe [] go may_b
With the appropriate RULES, it can be wrapped up in build and fuse properly.
I'd love to see this written as an unfoldr instead. Does anyone know if that's possible?
unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f = unfoldr (fmap f) . Just Note that unless unfoldr is inlined whenever its first argument is supplied, the use of (Maybe b) as the seed type means you'll get a lot more allocation and case analysis than in your direct definition. -- Live well, ~wren

On Fri, Aug 15, 2014 at 12:05 AM, wren romano
unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f = unfoldr (fmap f) . Just
Note that unless unfoldr is inlined whenever its first argument is supplied, the use of (Maybe b) as the seed type means you'll get a lot more allocation and case analysis than in your direct definition.
i.e., using (Maybe b) as the type of the seed used by unfoldr -- Live well, ~wren

On Aug 15, 2014 12:06 AM, "wren romano"
On Fri, Aug 15, 2014 at 12:05 AM, wren romano
wrote:
unfoldr1 :: (b -> (a, Maybe b)) -> b -> [a] unfoldr1 f = unfoldr (fmap f) . Just
Note that unless unfoldr is inlined whenever its first argument is supplied, the use of (Maybe b) as the seed type means you'll get a lot more allocation and case analysis than in your direct definition.
Although this seems to work out okay in isolation, it seems to lead to phase issues where the static constructor analysis (or whatever it's called) that makes the extra Maybe go away clashes in some timing fashion with other analyses, preventing some *other* optimizations from working. Or at least, that's what it looks like. I haven't entirely figured it out.
participants (2)
-
David Feuer
-
wren romano