[Haskell-cafe] list of range
PICCA Frederic-Emmanuel
frederic-emmanuel.picca at synchrotron-soleil.fr
Mon Oct 4 16:48:37 UTC 2021
> I am afraid, I still do not understand where you need the list of Ranges.
> In the original post you said, you want to parse a list of ranges like the
> one for pages to print in a printer dialog. Is it to select files from the
> 100 ones or is it to select images from the 300,000 ones? In the first
> case I would use IntMap, in the latter case I would use Interval data
> structures.
Yes exactly these range are there to select an hundred files from a series of thousans :).
then for each file I have the number of images.
at the end I have a dedicated type called Chunk which allows to split the stream
But you are right at this stage I do not need the initial range, since I already have the file name and the number of image
Cheers
data Chunk n a = Chunk !a !n !n
deriving instance (Show n, Show a) => Show (Chunk n a)
cweight :: Num n => Chunk n a -> n
cweight (Chunk _ l h) = h - l
csplit :: Num n => Chunk n a -> n -> (Chunk n a, Chunk n a)
csplit (Chunk a l h) n = (Chunk a l (l + n), Chunk a (l+n) h)
chunk :: (Num n, Ord n) => n -> [Chunk n a] -> [[Chunk n a]]
chunk target = go target target
where
go :: (Num n, Ord n) => n -> n -> [Chunk n a] -> [[Chunk n a]]
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 cs = (x : Prelude.head cs) : tail cs
golast tgt gap x =
if | cweight x <= gap -> [[x]]
| (x1, x2) <- csplit x gap -> [x1] : golast tgt tgt x2
{-# SPECIALIZE chunk :: Int -> [Chunk Int FilePath] -> [[Chunk Int FilePath]] #-}
More information about the Haskell-Cafe
mailing list