[Haskell-cafe] Improving *> and >> for Data.Sequence

Ross Paterson R.Paterson at city.ac.uk
Thu Nov 20 00:37:49 UTC 2014


On Wed, Nov 19, 2014 at 02:58:46PM -0500, David Feuer wrote:
> I got to looking at <*> just now, and it suggests the
> following question: is there a particularly efficient way to build a Seq when
> its ultimate size is known in advance, avoiding the usual incremental
> rebuilding?

The following avoids the rebuilding, but I haven't tweaked or timed it:

fromList' :: [a] -> Seq a
fromList' xs = Seq $ mkTree (Data.List.length xs) 1 $ map Elem xs

mkTree :: Int -> Int -> [a] -> FingerTree a
mkTree n size xs
  | n == 0 = Empty
  | n == 1 = let [x1] = xs in Single x1
  | n <  6 = let (l, r) = Data.List.splitAt (n `div` 2) xs in
      Deep totalSize (mkDigit l) Empty (mkDigit r)
  | otherwise = let
              size' = 3*size
              n' = (n-4) `div` 3
              digits = n - n'*3
              (l, rest) = Data.List.splitAt (digits `div` 2) xs
              (nodes, r) = getNodes n' size' rest
          in Deep totalSize (mkDigit l) (mkTree n' size' nodes) (mkDigit r)
  where
    totalSize = n*size

mkDigit :: [a] -> Digit a
mkDigit [x1] = One x1
mkDigit [x1, x2] = Two x1 x2
mkDigit [x1, x2, x3] = Three x1 x2 x3
mkDigit [x1, x2, x3, x4] = Four x1 x2 x3 x4

getNodes :: Int -> Int -> [a] -> ([Node a], [a])
getNodes n _ xs
  | n == 0 = ([], xs)
getNodes n size (x1:x2:x3:xs) = (Node3 size x1 x2 x3:ns, ys)
  where (ns, ys) = getNodes (n-1) size xs


More information about the Haskell-Cafe mailing list