[Haskell-cafe] a sort of chunk

Viktor Dukhovni ietf-dane at dukhovni.org
Mon Jan 20 08:29:17 UTC 2020


On Sun, Jan 19, 2020 at 11:17:54AM +0000, PICCA Frederic-Emmanuel wrote:

> ..., but this is not what I want :))
> 
> I want at the end to split each of my T into  chunk of length target.
> 
> like this
> 
> [[T "1" 0 10], [T "1" 10 20], [T "1" 20 30], [T "2" 0 10], ...]
> 
> So a split function like this should be used
> 
> split :: Int -> a -> (a, a)
> split s (T n f t) = (T n f s, T n s t)

    {-# LANGUAGE BangPatterns #-}
    {-# LANGUAGE MultiWayIf #-}
    {-# LANGUAGE StandaloneDeriving #-}

    data W n a = W !a !n !n
    deriving instance (Show n, Show a) => Show (W n a)

    wget :: W n a -> a
    wget (W a _ _) = a

    weight :: Num n => W n a -> n
    weight (W _ l h) = h - l

    wsplit :: Num n => W n a -> n -> (W n a, W n a)
    wsplit (W a l h) n = ( (W a l (l + n)), (W a (l+n) h) )

    chunk :: (Num n, Ord n) => n -> [W n a] -> [[W n a]]
    chunk target = go target target
      where
        go tgt _ []     = []
        go tgt gap [x] = golast tgt gap x
        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

    {-# SPECIALIZE chunk :: Int -> [W Int a] -> [[W Int a]]  #-}

-- 
    Viktor.


More information about the Haskell-Cafe mailing list