-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathBetterPredicate.hs
103 lines (78 loc) · 2.83 KB
/
BetterPredicate.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
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
module BetterPredicate where
import Control.Monad (filterM)
import System.Directory (Permissions(..), getModificationTime, getPermissions)
import System.Time (ClockTime(..))
import System.FilePath (takeExtension)
import Control.Exception (bracket, handle, SomeException)
import System.IO (IOMode(..), hClose, hFileSize, openFile)
import RecursiveContents (getRecursiveContents)
type Predicate = FilePath
-> Permissions
-> Maybe Integer
-> ClockTime
-> Bool
type Handler a = SomeException -> IO (Maybe a)
getFileSize :: FilePath -> IO (Maybe Integer)
getFileSize path = handle ((\_ -> return Nothing) :: Handler Integer) $
bracket (openFile path ReadMode) hClose $
\h -> (hFileSize h >>= return . Just)
simpleFileSize :: FilePath -> IO Integer
simpleFileSize path = do
h <- openFile path ReadMode
size <- hFileSize h
hClose h
return size
safeFileSize :: FilePath -> IO (Maybe Integer)
safeFileSize path = handle ((\_ -> return Nothing) :: SomeException -> IO (Maybe Integer)) $ do
h <- openFile path ReadMode
size <- hFileSize h
hClose h
return (Just size)
betterFind :: Predicate -> FilePath -> IO [FilePath]
betterFind p path = getRecursiveContents path >>= filterM check
where check name = do
perms <- getPermissions name
size <- getFileSize name
modified <- getModificationTime name
return (p name perms size modified)
myTest path _ (Just size) _ =
takeExtension path == ".cpp" && size > 131072
myTest _ _ _ _ = False
type InfoP a = FilePath
-> Permissions
-> Maybe Integer
-> ClockTime
-> a
pathP :: InfoP FilePath
pathP path _ _ _ = path
sizeP :: InfoP Integer
size _ _ (Just size) _ = size
sizeP _ _ Nothing _ = -1
equalP :: (Eq a) => InfoP a -> a -> InfoP Bool
equalP f k = \w x y z -> f w x y z == k
equalP' :: (Eq a) => InfoP a -> a -> InfoP Bool
equalP' f k w x y z = f w x y z == k
liftP :: (a -> b -> c) -> InfoP a -> b -> InfoP c
liftP q f k w x y z = f w x y z `q` k
greaterP, lesserP :: (Ord a) => InfoP a -> a -> InfoP Bool
greaterP = liftP (>)
lesserP = liftP (<)
simpleAndP :: InfoP Bool -> InfoP Bool -> InfoP Bool
simpleAndP f g w x y z = f w x y z && g w x y z
liftP2 :: (a -> b -> c) -> InfoP a -> InfoP b -> InfoP c
liftP2 q f g w x y z = f w x y z `q` g w x y z
andP = liftP2 (&&)
orP = liftP2 (||)
constP :: a -> InfoP a
constP k _ _ _ _ = k
liftPath :: (FilePath -> a) -> InfoP a
liftPath f w _ _ _ = f w
myTest2 = (liftPath takeExtension `equalP` ".cpp") `andP`
(sizeP `greaterP` 131072)
(==?) = equalP
infix 4 ==?
(&&?) = andP
infix 3 &&?
(>?) = greaterP
infix 4 >?
myTest3 = liftPath takeExtension ==? ".cpp" &&? sizeP >? 131072