Misleading strictness annotations in Data.List.NonEmpty
Oleg Grenrus
oleg.grenrus at iki.fi
Fri Jan 8 19:44:31 UTC 2021
Note also
-- | @since 4.9.0.0
instance Foldable NonEmpty where
foldr f z ~(a :| as) = f a (List.foldr f z as)
foldl f z (a :| as) = List.foldl f (f z a) as
foldl1 f (a :| as) = List.foldl f a as
-- GHC isn't clever enough to transform the default definition
-- into anything like this, so we'd end up shuffling a bunch of
-- Maybes around.
foldr1 f (p :| ps) = foldr go id ps p
where
go x r prev = f prev (r x)
-- We used to say
--
-- length (_ :| as) = 1 + length as
--
-- but the default definition is better, counting from 1.
--
-- The default definition also works great for null and foldl'.
-- As usual for cons lists, foldr' is basically hopeless.
foldMap f ~(a :| as) = f a `mappend` foldMap f as
fold ~(m :| ms) = m `mappend` fold ms
toList ~(a :| as) = a : as
Plenty of irrefutable patterns.
On 8.1.2021 21.41, David Feuer wrote:
> Yeah, the more I think about it, the more I like your stricter (<|). I
> don't see any really useful laziness to add to groupBy1. What were you
> thinking of?
>
> On Fri, Jan 8, 2021 at 2:27 PM Keith <keith.wygant at gmail.com> wrote:
>> There are a couple other ones that I'm less sure about.
>>
>> cons:
>> a <| ~(b :| bs) = a :| b : bs
>>
>> Unsugared this is
>> a <| bs = a :|
>> (case bs of b :| _ -> b ) :
>> case bs of _ :| bs -> bs
>>
>> Would this make more sense?
>> a <| bs = a :| case bs of b :| bs' -> b : bs'
>>
>> Then
>> cons x undefined = x :| undefined
>> not
>> x :| undefined : undefined
>>
>>
>> groupBy1 matches strictly, could be lazy. (Is this a performance issue or an oversight?)
>> —
>> Sent from my phone with K-9 Mail.
>>
>> On January 8, 2021 6:36:58 PM UTC, Keith <keith.wygant at gmail.com> wrote:
>>> Thanks, will do.
>>>
>>> On January 8, 2021 5:07:25 PM UTC, David Feuer <david.feuer at gmail.com> wrote:
>>>> The first one. Neither twiddles nor bangs are useful or add clarity.
>>>>
>>>> On Fri, Jan 8, 2021, 11:53 AM Keith <keith.wygant at gmail.com> wrote:
>>>>
>>>>> Currently:
>>>>>
>>>>> head ~(a :| _) = a
>>>>> tail ~(_ :| as) = as
>>>>>
>>>>> But head and tail are both strict. At best the '~'s have no effect.
>>>>>
>>>>> Should I open a PR to change it to
>>>>>
>>>>> head (a :| _) = a
>>>>> tail (_ :| as) = as
>>>>>
>>>>> or maybe even more clearly
>>>>>
>>>>> head !(a :l _) = a
>>>>> tail !(_ :| as) = as
>>>>>
>>>>> ?
>>>>> --Keith
>>>>> Sent from my phone with K-9 Mail.
>>>
>>>
>>> Good to know! Wasn't aware that that was in the works.
>>>
>>> And sorry for accidentally threading this onto something unrelated.
>>>
>>> -- Keith
>>> Sent from my phone with K-9 Mail.
>>>
>>> On January 8, 2021 5:13:31 PM UTC, Henning Thielemann <lemming at henning-thielemann.de> wrote:
>>>>
>>>> On Fri, 8 Jan 2021, Keith wrote:
>>>>
>>>>> Currently:
>>>>>
>>>>> head ~(a :| _) = a
>>>>> tail ~(_ :| as) = as
>>>>>
>>>>> But head and tail are both strict. At best the '~'s have no effect.
>>>>>
>>>>> Should I open a PR to change it to
>>>>>
>>>>> head (a :| _) = a
>>>>> tail (_ :| as) = as
>>>>>
>>>>> or maybe even more clearly
>>>>>
>>>>> head !(a :l _) = a
>>>>> tail !(_ :| as) = as
>>>>>
>>>>> ?
>>>>
>>>> The last one would trigger the "redundant bang pattern" warning that is
>>>> going to be implemented/released:
>>>> https://gitlab.haskell.org/ghc/ghc/issues/17340
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
More information about the Libraries
mailing list