[Haskell-cafe] a sort of chunk

Viktor Dukhovni ietf-dane at dukhovni.org
Mon Jan 20 10:39:16 UTC 2020


On Mon, Jan 20, 2020 at 10:03:16AM +0000, PICCA Frederic-Emmanuel wrote:

> chunk :: (Num n, Ord n) => n -> [Chunk n a] -> [[Chunk n a]]
> chunk target = go target target
>   where
>     go _ _ []          = []
>     go tgt gap [x]     = golast tgt gap x
>     go tgt gap ~(x:xs) =
>       let gap' = gap - cweight x
>       in if | gap' > 0                 -> cons1 x $ go tgt gap' xs
>             | gap' == 0                -> [x] : go tgt tgt xs
>             | (x1, x2) <- csplit x gap -> [x1] : go tgt tgt (x2 : xs)
> 
>     cons1 !x ~(c:cs) = (x : c) : cs
> 
>     golast tgt gap x =
>       if | cweight x <= gap         -> [x] : []
>          | (x1, x2) <- csplit x gap -> [x1] : golast tgt tgt x2

I've tried both GHC 8.6.5 and GHC 8.8.1, and get no warnings with either
"-O -Wall" or "-O2 -Wall" and the below (my original names, which look
equivalent).

    chunk :: (Num n, Ord n) => n -> [W n a] -> [[W n a]]
    chunk target = go target target
      where
        go _ _ []     = []
        go tgt gap [x] = golast tgt gap x
        -- XXX: Try dropping the "~" on the next line it should be redundant
        go tgt gap ~(x:xs) =
            let gap' = gap - weight x
             in if | gap' > 0  -> cons1 x $ go tgt gap' xs                                                                                           | gap' == 0 ->     [x] : go tgt tgt  xs
                   | (x1, x2)  <- wsplit x gap
                               -> [x1] : go tgt tgt (x2 : xs)
        cons1 !x ~(c:cs)    = (x : c) : cs
        golast tgt gap x =
            if | weight x <= gap -> [x] : []                                                                                                     | (x1, x2) <- wsplit x gap -> [x1] : golast tgt tgt x2

> But when compiling I have these warning 
> 
> > src/Hkl/Projects/Sixs.hs:(59,5)-(65,69): warning: [-Wincomplete-uni-patterns]
> >     Pattern match(es) are non-exhaustive
> >     In a pattern binding: Patterns not matched: []
> >    |
> > 59 |     go _ _ []          = []
> >    |     ^^^^^^^^^^^^^^^^^^^^^^^...
> 
> I do not understand this one

See the XXX comment I added above, with that and also
"-Wincomplete-uni-patterns" in addition to "-Wall", I no longer get that
warning.

> > src/Hkl/Projects/Sixs.hs:67:5-35: warning: [-Wincomplete-uni-patterns]
> >     Pattern match(es) are non-exhaustive
> >     In a pattern binding: Patterns not matched: []
> >    |
> > 67 |     cons1 !x ~(c:cs) = (x : c) : cs
> >    |     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> 
> If this is something which can not be reach, is it possible to explain to ghc how to avoid these warning ?

However, with "-Wincomplete-uni-patterns" I still get this one, but the
irrefutable binding is there for a reason, stricness in the second
argument has undesirable performance implications, we know that the list
won't be empty.  So perhaps compile this code in a module that does not
have that warning turned on.

It is not too difficult to rewrite "chunk" so that it operates on
(type-level) non-empty lists, but perhaps easier to just ignore or
disable the warning.

-- 
    Viktor.


More information about the Haskell-Cafe mailing list