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

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Fri May 10 02:24:46 UTC 2019


Make sense. I can see those "tricks" of C. But just, since this code
is not some complex computing, really wishing it could be speeded up.
For example, Rust gives Either on IO errors.

On Fri, May 10, 2019 at 10:17 AM Brandon Allbery <allbery.b at gmail.com> wrote:
>
> ...what?
>
> Also, in C you'd stat() and check for -1 (not found_ or inspect the result to see if it's what you want. But in Haskell this throws an exception instead of producing a sane Either. so you either make multiple syscalls or you have to catch an exception. So no matter what this ends up being higher overhead than C or Rust.
>
> On Thu, May 9, 2019 at 10:15 PM Magicloud Magiclouds <magicloud.magiclouds at gmail.com> wrote:
>>
>> I could not tell, since those are some kind of "standard" functions of
>> Haskell, right?
>>
>> On Fri, May 10, 2019 at 10:11 AM David Feuer <david.feuer at gmail.com> wrote:
>> >
>> > Pure speculation: are you paying for a lot of conversions between FilePath (string) and C strings?
>> >
>> > On Thu, May 9, 2019, 10:02 PM Magicloud Magiclouds <magicloud.magiclouds at gmail.com> 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)
>> >>
>> >>
>> >> --
>> >> 竹密岂妨流水过
>> >> 山高哪阻野云飞
>> >> _______________________________________________
>> >> Haskell-Cafe mailing list
>> >> To (un)subscribe, modify options or view archives go to:
>> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> >> Only members subscribed via the mailman list are allowed to post.
>>
>>
>>
>> --
>> 竹密岂妨流水过
>> 山高哪阻野云飞
>>
>> And for G+, please use magiclouds#gmail.com.
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
>
>
> --
> brandon s allbery kf8nh
> allbery.b at gmail.com



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.


More information about the Haskell-Cafe mailing list