-
Notifications
You must be signed in to change notification settings - Fork 104
/
findpar3.hs
81 lines (72 loc) · 2.05 KB
/
findpar3.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
{-# LANGUAGE BangPatterns,CPP #-}
import System.Directory
import System.FilePath
import Control.Concurrent.Async
import System.Environment
import Data.List hiding (find)
import Control.Exception (finally)
import Data.Maybe (isJust)
import Control.Concurrent.MVar
import Control.Concurrent.STM
import Data.IORef
import GHC.Conc (getNumCapabilities)
import CasIORef
-- <<main
main = do
[s,d] <- getArgs
n <- getNumCapabilities
sem <- newNBSem (if n == 1 then 0 else n * 4)
find sem s d >>= print
-- >>
-- <<find
find :: NBSem -> String -> FilePath -> IO (Maybe FilePath)
find sem s d = do
fs <- getDirectoryContents d
let fs' = sort $ filter (`notElem` [".",".."]) fs
if any (== s) fs'
then return (Just (d </> s))
else do
let ps = map (d </>) fs' -- <1>
foldr (subfind sem s) dowait ps [] -- <2>
where
dowait as = loop (reverse as) -- <3>
loop [] = return Nothing
loop (a:as) = do -- <4>
r <- wait a -- <5>
case r of
Nothing -> loop as -- <6>
Just a -> return (Just a) -- <7>
-- >>
-- <<subfind
subfind :: NBSem -> String -> FilePath
-> ([Async (Maybe FilePath)] -> IO (Maybe FilePath))
-> [Async (Maybe FilePath)] -> IO (Maybe FilePath)
subfind sem s p inner asyncs = do
isdir <- doesDirectoryExist p
if isdir
then do
q <- tryWaitNBSem sem
if q
then withAsync (find sem s p `finally` signalNBSem sem) $ \a ->
inner (a:asyncs)
else do r <- find sem s p
if isJust r then return r else inner asyncs
else inner asyncs
-- >>
-- <<NBSem
newtype NBSem = NBSem (IORef Int)
newNBSem :: Int -> IO NBSem
newNBSem i = do
m <- newIORef i
return (NBSem m)
tryWaitNBSem :: NBSem -> IO Bool
tryWaitNBSem (NBSem m) = do
atomicModifyIORef m $ \i ->
if i == 0
then (i, False)
else let !z = i-1 in (z, True)
signalNBSem :: NBSem -> IO ()
signalNBSem (NBSem m) =
atomicModifyIORef m $ \i ->
let !z = i+1 in (z, ())
-- >>