分析/改善内存使用和/或 GC 时间

2024-04-11

Original

我正在尝试聚合 CSV 文件并遇到 [我认为] 过多的内存使用和/或 GC 工作。当团体数量增加时,这个问题似乎就会出现。当键达到数百或数千时没有问题,但当键达到数万时很快就会开始在 GC 中花费大部分时间。

Update

搬家自Data.ByteString.Lazy.ByteString to Data.ByteString.Short.ShortByteString显着减少了内存消耗(达到我认为合理的水平)。然而,GC 所花费的时间似乎仍然远远高于我预期的必要时间。我从Data.HashMap.Strict.HashMap to Data.HashTable.ST.Basic.HashTable看看是否有突变ST会有帮助,但似乎没有帮助。以下是目前完整的测试代码,包括generateFile创建测试样本:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import System.IO (withFile, IOMode(WriteMode))
import qualified System.Random as Random

import qualified Data.ByteString.Short as BSS
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
import qualified Control.Monad.ST as ST

import qualified Data.HashTable.ST.Basic as HT
import qualified Data.HashTable.Class as HT (toList)
import Data.Hashable (Hashable, hashWithSalt)

import Data.List (unfoldr)

import qualified Data.Traversable as T
import Control.Monad (forM_)

instance Hashable a => Hashable (V.Vector a) where
  hashWithSalt s = hashWithSalt s . V.toList

data CSVFormat = CSVFormat {
  csvSeparator :: Char,
  csvWrapper :: Char
}

readCSV :: CSVFormat -> Int -> FilePath -> IO [V.Vector BSS.ShortByteString]
readCSV format skip filepath = BL.readFile filepath >>= return . parseCSV format skip

parseCSV :: CSVFormat -> Int -> BL.ByteString -> [V.Vector BSS.ShortByteString]
parseCSV (CSVFormat sep wrp) skp = drop skp . unfoldr (\bs -> if BL.null bs then Nothing else Just (apfst V.fromList (parseLine bs)))
  where
    {-# INLINE apfst #-}
    apfst f (x,y) = (f x,y)

    {-# INLINE isCr #-}
    isCr c = c == '\r'

    {-# INLINE isLf #-}
    isLf c = c == '\n'

    {-# INLINE isSep #-}
    isSep c = c == sep || isLf c || isCr c

    {-# INLINE isWrp #-}
    isWrp c = c == wrp

    {-# INLINE parseLine #-}
    parseLine :: BL.ByteString -> ([BSS.ShortByteString], BL.ByteString)
    parseLine bs =
      let (field,bs') = parseField bs in
      case BL.uncons bs' of
        Just (c,bs1)
          | isLf c -> (field : [],bs1)
          | isCr c ->
              case BL.uncons bs1 of
                Just (c,bs2) | isLf c -> (field : [],bs2)
                _ -> (field : [],bs1)
          | otherwise -> apfst (field :) (parseLine bs1)
        Nothing -> (field : [],BL.empty)

    {-# INLINE parseField #-}
    parseField :: BL.ByteString -> (BSS.ShortByteString, BL.ByteString)
    parseField bs =
      case BL.uncons bs of
        Just (c,bs')
          | isWrp c -> apfst (BSS.toShort . BL.toStrict . BL.concat) (parseEscaped bs')
          | otherwise -> apfst (BSS.toShort . BL.toStrict) (BL.break isSep bs)
        Nothing -> (BSS.empty,BL.empty)

    {-# INLINE parseEscaped #-}
    parseEscaped :: BL.ByteString -> ([BL.ByteString], BL.ByteString)
    parseEscaped bs =
      let (chunk,bs') = BL.break isWrp bs in
      case BL.uncons bs' of
        Just (_,bs1) ->
          case BL.uncons bs1 of
            Just (c,bs2)
              | isWrp c -> apfst (\xs -> chunk : BL.singleton wrp : xs) (parseEscaped bs2)
              | otherwise -> (chunk : [],bs1)
            Nothing -> (chunk : [],BL.empty)
        Nothing -> error "EOF within quoted string"

aggregate :: [Int]
          -> Int
          -> [V.Vector BSS.ShortByteString]
          -> [V.Vector BSS.ShortByteString]
aggregate groups size records =
  let indices = [0..size - 1] in

  ST.runST $ do
    state <- HT.new

    forM_ records (\record -> do
        let key = V.fromList (map (\g -> record V.! g) groups)

        existing <- HT.lookup state key
        case existing of
          Just x ->
            forM_ indices (\i -> do
                current <- MV.read x i
                MV.write x i $! const current (record V.! i)
              )
          Nothing -> do
            x <- MV.new size
            forM_ indices (\i -> MV.write x i $! record V.! i)
            HT.insert state key x
      )

    HT.toList state >>= T.traverse V.unsafeFreeze . map snd

filedata :: IO ([Int],Int,[V.Vector BSS.ShortByteString])
filedata = do
  records <- readCSV (CSVFormat ',' '"') 1 "file.csv"
  return ([0,1,2],18,records)

main :: IO ()
main = do
  (key,len,records) <- filedata
  print (length (aggregate key len records))

generateFile :: IO ()
generateFile = do
  withFile "file.csv" WriteMode $ \handle -> do
    forM_ [0..650000] $ \_ -> do
      x <- BL.pack . show . truncate . (* 15 ) <$> (Random.randomIO :: IO Double)
      y <- BL.pack . show . truncate . (* 50 ) <$> (Random.randomIO :: IO Double)
      z <- BL.pack . show . truncate . (* 200) <$> (Random.randomIO :: IO Double)
      BL.hPut handle (BL.intercalate "," (x:y:z:replicate 15 (BL.replicate 20 ' ')))
      BL.hPut handle "\n"

我收到以下分析结果:

17,525,392,208 bytes allocated in the heap
27,394,021,360 bytes copied during GC
   285,382,192 bytes maximum residency (129 sample(s))
     3,714,296 bytes maximum slop
           831 MB total memory in use (0 MB lost due to fragmentation)

                                   Tot time (elapsed)  Avg pause  Max pause
Gen  0       577 colls,     0 par    1.576s   1.500s     0.0026s    0.0179s
Gen  1       129 colls,     0 par   25.335s  25.663s     0.1989s    0.2889s

TASKS: 3 (1 bound, 2 peak workers (2 total), using -N1)

SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)

INIT    time    0.000s  (  0.002s elapsed)
MUT     time   11.965s  ( 23.939s elapsed)
GC      time   15.148s  ( 15.400s elapsed)
RP      time    0.000s  (  0.000s elapsed)
PROF    time   11.762s  ( 11.763s elapsed)
EXIT    time    0.000s  (  0.088s elapsed)
Total   time   38.922s  ( 39.429s elapsed)

Alloc rate    1,464,687,582 bytes per MUT second

Productivity  30.9% of total user, 30.5% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync: 0
gen[1].sync: 0

And the following heap visualization: Heap visualization


原来这是V.!调用不够严格。将它们替换为indexM大大减少了内存消耗。

本文内容由网友自发贡献,版权归原作者所有,本站不承担相应法律责任。如您发现有涉嫌抄袭侵权的内容,请联系:hwhale#tublm.com(使用前将#替换为@)

分析/改善内存使用和/或 GC 时间 的相关文章

随机推荐

  • XCode 库搜索路径

    对于我的 iOS 项目 我有一个特定的文件夹结构 root src xcode MyProject
  • 提取两个给定字符串之间的文本

    希望有人可以帮助我 现在已经遍布谷歌了 我正在对文档进行一些区域 ocr 并且想使用正则表达式提取一些文本 总是这样 直到 姓名 姓名 org nr 12323123 我想提取名称部分 它可以是 1 4 个名称 但 Til 和 org nr
  • 大数组的堆栈溢出,但同样大的向量的堆栈溢出?

    今天我在处理大型数据结构时遇到了一个有趣的问题 我最初使用向量来存储超过 1000000 个整数 但后来决定我实际上并不需要向量的动态功能 无论如何 我在声明后就保留了 1000000 个位置 相反 这将是有益的 能够在数据结构中的任何位置
  • 如何禁用 PHP 中的线程安全?

    我正在使用一些需要禁用线程安全的软件 我正在 Windows 服务器上工作 根据我在其他地方读到的内容 我不能只在 ini 文件中配置它 这是真的 如果是这样 我将如何编译它以关闭线程安全 您必须在禁用 ZTS 的情况下编译 PHP 编译标
  • MATLAB 中的 .m 和 .mat 文件有什么区别

    当我跟踪我的参考 MATLAB 脚本时 我发现了带有以下内容的文件 mat扩大 我的问题是 有什么区别 mat and m files 如何使用打开文件 mat扩大 扩展名为 m 的文件包含 MATLAB 代码 其形式为script htt
  • 移动设备上的 jQuery 实时滚动事件(解决方法)

    老问题 当用户在移动网站或应用程序 Web 视图 上滚动元素时触发滚动事件 我所寻找的只是访问正确的scrollTop 当用户在移动设备上滚动我的页面时获取该值 而不是在用户停止时获取它 我确信在某个地方有一个解决方法 如果我是正确的话 这
  • iOS:从背景图像中检索矩形图像

    我正在开发一个实现 其中我在大背景图像中有一个矩形图像 我正在尝试以编程方式从大图像中检索矩形图像 并从该特定矩形图像中检索文本信息 我正在尝试使用 Open CV 第三方框架 但无法从大背景图像中检索矩形图像 有人可以指导我 我怎样才能实
  • 如何使用 JSZip 使用 Node.js 中的缓冲区内容生成 zip 文件?

    我有一个字符串数组 应将其写入 txt 文件 另外 我需要使用 JSZip 将生成的 txt 文件压缩为 zip 格式 在客户端 我能够使用该字符串数组生成 文本 纯文本 Blob 然后使用 JSZip 将此 Blob 压缩为 zip 格式
  • .NET 6 混淆

    我试图使用 生成单个文件 选项来混淆编译 NET 6 项目后获得的 exe 文件 问题是没有混淆器对其起作用 我想知道是否有人知道为什么 预先感谢您的回答 您必须混淆位于 obj Release net6 0 windows win x64
  • 为分组依据字段创建索引?

    Oracle数据库中需要为group by字段创建索引吗 例如 select from some table where field one is not null and field two group by field three fi
  • 编码 NSAttributedString 会引发错误

    根据已接受的答案这个问题 https stackoverflow com questions 2626667 saving custom attributes in nsattributedstring 我写了以下代码 NSData som
  • Angular 2 中的访问控制允许来源问题

    我在从 Node js 服务器获取数据时遇到问题 客户端是 public getTestLines Observable
  • “变量”变量名c++

    问题 我在这里搜索了一段时间 寻找一种循环遍历名为有点像的变量的方法variable 1 variable 2 variable n 基本上 我问是否有一种方法可以使用循环来实现variable i或者 更具体地说 就我而言 functio
  • 如何使ODP.NET 4.0(64位)在64位机Windows 7上运行?

    我已经使用 Oracle 提供的 XCopy 11 2 安装了 64 位计算机的 Oracle 客户端 按照自述说明安装了所有内容 我正在使用 Visual Studio 2010 该项目的类型为 ASP NET 网站 当我尝试使用上面安装
  • app.module.ts 中的environment.product变量始终为true

    我试图在我的 app module 文件中设置一个配置设置 以便它根据我是否在生产中而有所不同 My environment ts文件有 export const environment production false My enviro
  • 即使 EditText 不可编辑,EditText 光标也可见

    我需要在一个中引入数据EditText但我想使用虚拟键盘 而不是安卓键盘 如果我使用setKeyListener null 即使使用后光标也是不可见的setCursorVisible true 是否有可能制作一个EditText即使它不可编
  • 是否可以将 Primefaces 和 Richfaces 结合到一个 Web 应用程序中?

    看完之后RichFaces 与 PrimeFaces 针对性能 https stackoverflow com questions 3402952 richfaces vs primefaces 我很想在我的 Web 应用程序中同时使用两者
  • 在 Windows 10 版本中找不到 SettingsPane

    我正在使用 Visual Studio 2015 构建一个新的 Windows 10 UWP 通用 Windows 平台 应用程序 实际上 我正在移植我的 Windows 8 1 应用程序 但我是通过创建一个全新的项目并手动拉入每个类来实现
  • 如何使用 git 作为 SQL Server Management Studio 的源代码控制提供程序

    我们可以使用GIT作为sql management studio的源代码管理吗 用于 SSMS 中的数据库源代码控制 代理 SVN SCC Subversion 插件 http www zeusedit com agent ssms ms
  • 分析/改善内存使用和/或 GC 时间

    Original 我正在尝试聚合 CSV 文件并遇到 我认为 过多的内存使用和 或 GC 工作 当团体数量增加时 这个问题似乎就会出现 当键达到数百或数千时没有问题 但当键达到数万时很快就会开始在 GC 中花费大部分时间 Update 搬家