assistant: Fixed several minor memory leaks that manifested when adding a large number of files.
This commit is contained in:
parent
404c750489
commit
b92b54bd42
9 changed files with 39 additions and 19 deletions
|
@ -5,7 +5,7 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings, CPP #-}
|
{-# LANGUAGE OverloadedStrings, CPP, BangPatterns #-}
|
||||||
|
|
||||||
module Assistant.Alert where
|
module Assistant.Alert where
|
||||||
|
|
||||||
|
@ -367,8 +367,8 @@ fileAlert msg files = (activityAlert Nothing shortfiles)
|
||||||
where
|
where
|
||||||
maxfilesshown = 10
|
maxfilesshown = 10
|
||||||
|
|
||||||
(somefiles, counter) = splitcounter (dedupadjacent files)
|
(!somefiles, !counter) = splitcounter (dedupadjacent files)
|
||||||
shortfiles = map (fromString . shortFile . takeFileName) somefiles
|
!shortfiles = map (fromString . shortFile . takeFileName) somefiles
|
||||||
|
|
||||||
renderer alert = tenseWords $ msg : alertData alert ++ showcounter
|
renderer alert = tenseWords $ msg : alertData alert ++ showcounter
|
||||||
where
|
where
|
||||||
|
@ -391,9 +391,9 @@ fileAlert msg files = (activityAlert Nothing shortfiles)
|
||||||
in (keep, length rest)
|
in (keep, length rest)
|
||||||
|
|
||||||
combiner new old =
|
combiner new old =
|
||||||
let (fs, n) = splitcounter $
|
let (!fs, n) = splitcounter $
|
||||||
dedupadjacent $ alertData new ++ alertData old
|
dedupadjacent $ alertData new ++ alertData old
|
||||||
cnt = n + alertCounter new + alertCounter old
|
!cnt = n + alertCounter new + alertCounter old
|
||||||
in old
|
in old
|
||||||
{ alertData = fs
|
{ alertData = fs
|
||||||
, alertCounter = cnt
|
, alertCounter = cnt
|
||||||
|
|
|
@ -13,7 +13,7 @@ import Utility.Tense
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map.Strict as M
|
||||||
|
|
||||||
{- This is as many alerts as it makes sense to display at a time.
|
{- This is as many alerts as it makes sense to display at a time.
|
||||||
- A display might be smaller, or larger, the point is to not overwhelm the
|
- A display might be smaller, or larger, the point is to not overwhelm the
|
||||||
|
@ -122,7 +122,7 @@ mergeAlert i al m = maybe updatePrune updateCombine (alertCombiner al)
|
||||||
let (f, rest) = partition (\(_, a) -> isFiller a) l
|
let (f, rest) = partition (\(_, a) -> isFiller a) l
|
||||||
in drop bloat f ++ rest
|
in drop bloat f ++ rest
|
||||||
updatePrune = pruneBloat $ M.filterWithKey pruneSame $
|
updatePrune = pruneBloat $ M.filterWithKey pruneSame $
|
||||||
M.insertWith' const i al m
|
M.insert i al m
|
||||||
updateCombine combiner =
|
updateCombine combiner =
|
||||||
let combined = M.mapMaybe (combiner al) m
|
let combined = M.mapMaybe (combiner al) m
|
||||||
in if M.null combined
|
in if M.null combined
|
||||||
|
|
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module Assistant.DaemonStatus where
|
module Assistant.DaemonStatus where
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
|
@ -23,7 +25,7 @@ import System.Posix.Types
|
||||||
import Data.Time.Clock.POSIX
|
import Data.Time.Clock.POSIX
|
||||||
import Data.Time
|
import Data.Time
|
||||||
import System.Locale
|
import System.Locale
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map.Strict as M
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
|
||||||
getDaemonStatus :: Assistant DaemonStatus
|
getDaemonStatus :: Assistant DaemonStatus
|
||||||
|
@ -37,7 +39,7 @@ modifyDaemonStatus a = do
|
||||||
dstatus <- getAssistant daemonStatusHandle
|
dstatus <- getAssistant daemonStatusHandle
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
(s, b) <- atomically $ do
|
(s, b) <- atomically $ do
|
||||||
r@(s, _) <- a <$> takeTMVar dstatus
|
r@(!s, _) <- a <$> takeTMVar dstatus
|
||||||
putTMVar dstatus s
|
putTMVar dstatus s
|
||||||
return r
|
return r
|
||||||
sendNotification $ changeNotifier s
|
sendNotification $ changeNotifier s
|
||||||
|
@ -153,7 +155,8 @@ tenMinutes = 10 * 60
|
||||||
adjustTransfersSTM :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> STM ()
|
adjustTransfersSTM :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> STM ()
|
||||||
adjustTransfersSTM dstatus a = do
|
adjustTransfersSTM dstatus a = do
|
||||||
s <- takeTMVar dstatus
|
s <- takeTMVar dstatus
|
||||||
putTMVar dstatus $ s { currentTransfers = a (currentTransfers s) }
|
let !v = a (currentTransfers s)
|
||||||
|
putTMVar dstatus $ s { currentTransfers = v }
|
||||||
|
|
||||||
{- Checks if a transfer is currently running. -}
|
{- Checks if a transfer is currently running. -}
|
||||||
checkRunningTransferSTM :: DaemonStatusHandle -> Transfer -> STM Bool
|
checkRunningTransferSTM :: DaemonStatusHandle -> Transfer -> STM Bool
|
||||||
|
@ -168,7 +171,7 @@ alterTransferInfo t a = updateTransferInfo' $ M.adjust a t
|
||||||
- or if already present, updates it while preserving the old transferTid,
|
- or if already present, updates it while preserving the old transferTid,
|
||||||
- transferPaused, and bytesComplete values, which are not written to disk. -}
|
- transferPaused, and bytesComplete values, which are not written to disk. -}
|
||||||
updateTransferInfo :: Transfer -> TransferInfo -> Assistant ()
|
updateTransferInfo :: Transfer -> TransferInfo -> Assistant ()
|
||||||
updateTransferInfo t info = updateTransferInfo' $ M.insertWith' merge t info
|
updateTransferInfo t info = updateTransferInfo' $ M.insertWith merge t info
|
||||||
where
|
where
|
||||||
merge new old = new
|
merge new old = new
|
||||||
{ transferTid = maybe (transferTid new) Just (transferTid old)
|
{ transferTid = maybe (transferTid new) Just (transferTid old)
|
||||||
|
@ -213,8 +216,8 @@ addAlert alert = do
|
||||||
where
|
where
|
||||||
add s = (s { lastAlertId = i, alertMap = m }, i)
|
add s = (s { lastAlertId = i, alertMap = m }, i)
|
||||||
where
|
where
|
||||||
i = nextAlertId $ lastAlertId s
|
!i = nextAlertId $ lastAlertId s
|
||||||
m = mergeAlert i alert (alertMap s)
|
!m = mergeAlert i alert (alertMap s)
|
||||||
|
|
||||||
removeAlert :: AlertId -> Assistant ()
|
removeAlert :: AlertId -> Assistant ()
|
||||||
removeAlert i = updateAlert i (const Nothing)
|
removeAlert i = updateAlert i (const Nothing)
|
||||||
|
@ -225,7 +228,9 @@ updateAlert i a = updateAlertMap $ \m -> M.update a i m
|
||||||
updateAlertMap :: (AlertMap -> AlertMap) -> Assistant ()
|
updateAlertMap :: (AlertMap -> AlertMap) -> Assistant ()
|
||||||
updateAlertMap a = notifyAlert `after` modifyDaemonStatus_ update
|
updateAlertMap a = notifyAlert `after` modifyDaemonStatus_ update
|
||||||
where
|
where
|
||||||
update s = s { alertMap = a (alertMap s) }
|
update s =
|
||||||
|
let !m = a (alertMap s)
|
||||||
|
in s { alertMap = a (alertMap s) }
|
||||||
|
|
||||||
{- Displays an alert while performing an activity that returns True on
|
{- Displays an alert while performing an activity that returns True on
|
||||||
- success.
|
- success.
|
||||||
|
|
|
@ -13,7 +13,7 @@ import qualified Types.Remote as Remote
|
||||||
|
|
||||||
import Data.Function
|
import Data.Function
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map.Strict as M
|
||||||
|
|
||||||
{- Blocks until there is a remote or remotes that need to be scanned.
|
{- Blocks until there is a remote or remotes that need to be scanned.
|
||||||
-
|
-
|
||||||
|
|
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module Assistant.TransferQueue (
|
module Assistant.TransferQueue (
|
||||||
TransferQueue,
|
TransferQueue,
|
||||||
Schedule(..),
|
Schedule(..),
|
||||||
|
@ -32,7 +34,7 @@ import Annex.Wanted
|
||||||
import Utility.TList
|
import Utility.TList
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map.Strict as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
||||||
type Reason = String
|
type Reason = String
|
||||||
|
@ -189,7 +191,7 @@ getNextTransfer acceptable = do
|
||||||
if acceptable info
|
if acceptable info
|
||||||
then do
|
then do
|
||||||
adjustTransfersSTM dstatus $
|
adjustTransfersSTM dstatus $
|
||||||
M.insertWith' const t info
|
M.insert t info
|
||||||
return $ Just r
|
return $ Just r
|
||||||
else return Nothing
|
else return Nothing
|
||||||
|
|
||||||
|
@ -217,7 +219,8 @@ dequeueTransfers c = do
|
||||||
|
|
||||||
dequeueTransfersSTM :: TransferQueue -> (Transfer -> Bool) -> STM [(Transfer, TransferInfo)]
|
dequeueTransfersSTM :: TransferQueue -> (Transfer -> Bool) -> STM [(Transfer, TransferInfo)]
|
||||||
dequeueTransfersSTM q c = do
|
dequeueTransfersSTM q c = do
|
||||||
(removed, ts) <- partition (c . fst) <$> readTList (queuelist q)
|
!(removed, ts) <- partition (c . fst) <$> readTList (queuelist q)
|
||||||
void $ writeTVar (queuesize q) (length ts)
|
let !len = length ts
|
||||||
|
void $ writeTVar (queuesize q) len
|
||||||
setTList (queuelist q) ts
|
setTList (queuelist q) ts
|
||||||
return removed
|
return removed
|
||||||
|
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -18,6 +18,8 @@ git-annex (5.20131231) UNRELEASED; urgency=medium
|
||||||
* addurl, importfeed: Honor annex.diskreserve as long as the size of the
|
* addurl, importfeed: Honor annex.diskreserve as long as the size of the
|
||||||
url can be checked.
|
url can be checked.
|
||||||
* add: Fix rollback when disk is completely full.
|
* add: Fix rollback when disk is completely full.
|
||||||
|
* assistant: Fixed several minor memory leaks that manifested when
|
||||||
|
adding a large number of files.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Tue, 31 Dec 2013 13:41:18 -0400
|
-- Joey Hess <joeyh@debian.org> Tue, 31 Dec 2013 13:41:18 -0400
|
||||||
|
|
||||||
|
|
|
@ -1596,3 +1596,13 @@ rsync error: error in rsync protocol data stream (code 12) at io.c(605) [sender=
|
||||||
|
|
||||||
# End of transcript or log.
|
# End of transcript or log.
|
||||||
"""]]
|
"""]]
|
||||||
|
|
||||||
|
> [[Fixed|done]]. This was several garden-variety haskell laziness leaks,
|
||||||
|
> all fixed by adding strictness annotations.
|
||||||
|
>
|
||||||
|
> Before: [[leakbefore.png]]
|
||||||
|
> After: [[leakafter.png]]
|
||||||
|
>
|
||||||
|
> Looks like I got them all, and it returns to running in constant space
|
||||||
|
> after adding and uploading the files (which can take memory porportional
|
||||||
|
> to the number of files that were added/changed at once). --[[Joey]]
|
||||||
|
|
BIN
doc/bugs/import_memleak_from_the_assistant/leakafter.png
Normal file
BIN
doc/bugs/import_memleak_from_the_assistant/leakafter.png
Normal file
Binary file not shown.
After Width: | Height: | Size: 42 KiB |
BIN
doc/bugs/import_memleak_from_the_assistant/leakbefore.png
Normal file
BIN
doc/bugs/import_memleak_from_the_assistant/leakbefore.png
Normal file
Binary file not shown.
After Width: | Height: | Size: 23 KiB |
Loading…
Add table
Add a link
Reference in a new issue