File: FindFile001.hs

package info (click to toggle)
ghc 9.6.6-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, trixie
  • size: 158,216 kB
  • sloc: haskell: 648,228; ansic: 81,656; cpp: 11,808; javascript: 8,444; sh: 5,831; fortran: 3,527; python: 3,277; asm: 2,523; makefile: 2,298; yacc: 1,570; lisp: 532; xml: 196; perl: 145; csh: 2
file content (54 lines) | stat: -rw-r--r-- 1,791 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE CPP #-}
module FindFile001 where
#include "util.inl"
import qualified Data.List as List
import System.Directory.Internal
import System.OsPath ((</>))

main :: TestEnv -> IO ()
main _t = do

  createDirectory "bar"
  createDirectory "qux"
  writeFile "foo" ""
  writeFile (so ("bar" </> "foo")) ""
  writeFile (so ("qux" </> "foo")) ":3"

  -- make sure findFile is lazy enough
  T(expectEq) () (Just ("." </> "foo")) =<< findFile ("." : undefined) "foo"

  -- make sure relative paths work
  T(expectEq) () (Just ("." </> "bar" </> "foo")) =<<
    findFile ["."] ("bar" </> "foo")

  T(expectEq) () (Just ("." </> "foo")) =<< findFile [".", "bar"] ("foo")
  T(expectEq) () (Just ("bar" </> "foo")) =<< findFile ["bar", "."] ("foo")

  let f fn = (== ":3") <$> readFile (so fn)
  for_ (List.permutations ["qux", "bar", "."]) $ \ ds -> do

    let (match, noMatch) = List.partition (== "qux") ds
    match0 : _ <- pure match
    noMatch0 : _ <- pure noMatch

    T(expectEq) ds (Just (match0 </> "foo")) =<<
      findFileWith f ds "foo"

    T(expectEq) ds ((</> "foo") <$> match) =<< findFilesWith f ds "foo"

    T(expectEq) ds (Just (noMatch0 </> "foo")) =<<
      findFileWith ((not <$>) . f) ds "foo"

    T(expectEq) ds ((</> "foo") <$> noMatch) =<<
      findFilesWith ((not <$>) . f) ds "foo"

    T(expectEq) ds Nothing =<< findFileWith (\ _ -> return False) ds "foo"

    T(expectEq) ds [] =<< findFilesWith (\ _ -> return False) ds "foo"

  -- make sure absolute paths are handled properly irrespective of 'dirs'
  -- https://github.com/haskell/directory/issues/72
  absPath <- makeAbsolute ("bar" </> "foo")
  absPath2 <- makeAbsolute ("bar" </> "nonexistent")
  T(expectEq) () (Just absPath) =<< findFile [] absPath
  T(expectEq) () Nothing =<< findFile [] absPath2