[Haskell-cafe] How to optimize a directory scanning?

Vanessa McHale vanessa.mchale at iohk.io
Fri May 10 02:12:59 UTC 2019


Would you happen to have the Rust/C code available?

One option is to simply using the C code and bind to it.

The one thing that stands out to me in your code is that you call

doesDirectoryExist

as well as

getFileStatus

when you could determine whether it exists with

doesPathExist

and then determine whether it's a directory by checking the result of
getFileStatus

Cheers,
Vanessa McHale

On 5/9/19 9:00 PM, Magicloud Magiclouds wrote:
> Hi,
> I have asked this in Stackoverflow without getting an answer.
> Wondering if people here could have some thoughts.
>
> I have a function reading the content of /proc every second.
> Surprisingly, its CPU usage in top is around 5%, peak at 8%. But same
> logic in C or Rust just takes like 1% or 2%. Wondering if this can be
> improved. /proc is virtual filesystem, so this is not related to HDD
> performance. And I noticed this difference because my CPU is too old
> (Core Gen2). On modern CPU, as tested by others, the difference is
> barely noticeable.
>
> import Control.Exception
> import Control.Concurrent
> import Control.Monad
> import Data.Char
> import Data.Maybe
> import System.Directory
> import System.FilePath
> import System.Posix.Files
> import System.Posix.Signals
> import System.Posix.Types
> import System.Posix.User
> import System.IO.Strict as Strict
>
> watch u limit0s limit0h = do
>   listDirectory "/proc/" >>= mapM_ (\fp -> do
>     isMyPid' <- maybe False id <$> wrap2Maybe (isMyPid fp u)
>     wrap2Maybe (Strict.readFile ("/proc/" </> fp </> "stat")))
>   threadDelay 1000000
>   watch u limit0s limit0h
>   where
>     wrap2Maybe :: IO a -> IO (Maybe a)
>     wrap2Maybe f = catch ((<$>) Just $! f) (\(_ :: IOException) ->
> return Nothing)
>     isMyPid :: FilePath -> UserID -> IO Bool
>     isMyPid fp me = do
>       let areDigit = fp >= "0" && fp <= "9"
>       isDir <- doesDirectoryExist $ "/proc/" </> fp
>       owner <- fileOwner <$> getFileStatus ("/proc" </> fp)
>       return $ areDigit && isDir && (owner == me)
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190509/7dcd19ee/attachment-0001.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 488 bytes
Desc: OpenPGP digital signature
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190509/7dcd19ee/attachment-0001.sig>


More information about the Haskell-Cafe mailing list