Proposal: add unfoldr1 to the somewhere in base

David Feuer david.feuer at gmail.com
Fri Aug 1 23:41:46 UTC 2014


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 <david.feuer at gmail.com> wrote:
> 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?


More information about the Libraries mailing list