{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
module Development.Shake.Internal.Rules.Directory(
    doesFileExist, doesDirectoryExist,
    getDirectoryContents, getDirectoryFiles, getDirectoryDirs,
    getEnv, getEnvWithDefault, getEnvError,
    removeFiles, removeFilesAfter,
    getDirectoryFilesIO,
    defaultRuleDirectory
    ) where
import Control.Exception.Extra
import Control.Monad.Extra
import Control.Monad.IO.Class
import Data.Maybe
import Data.Binary
import Data.List
import Data.Tuple.Extra
import qualified Data.HashSet as Set
import qualified System.Directory as IO
import qualified System.Environment as IO
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Action
import Development.Shake.Internal.Core.Rules
import Development.Shake.Internal.Core.Build
import Development.Shake.Internal.Value
import Development.Shake.Classes
import Development.Shake.FilePath
import Development.Shake.Internal.FilePattern
import General.Extra
import General.Binary
type instance RuleResult DoesFileExistQ = DoesFileExistA
newtype DoesFileExistQ = DoesFileExistQ FilePath
    deriving (Typeable,DoesFileExistQ -> DoesFileExistQ -> Bool
(DoesFileExistQ -> DoesFileExistQ -> Bool)
-> (DoesFileExistQ -> DoesFileExistQ -> Bool) -> Eq DoesFileExistQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoesFileExistQ -> DoesFileExistQ -> Bool
$c/= :: DoesFileExistQ -> DoesFileExistQ -> Bool
== :: DoesFileExistQ -> DoesFileExistQ -> Bool
$c== :: DoesFileExistQ -> DoesFileExistQ -> Bool
Eq,Int -> DoesFileExistQ -> Int
DoesFileExistQ -> Int
(Int -> DoesFileExistQ -> Int)
-> (DoesFileExistQ -> Int) -> Hashable DoesFileExistQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DoesFileExistQ -> Int
$chash :: DoesFileExistQ -> Int
hashWithSalt :: Int -> DoesFileExistQ -> Int
$chashWithSalt :: Int -> DoesFileExistQ -> Int
Hashable,Get DoesFileExistQ
[DoesFileExistQ] -> Put
DoesFileExistQ -> Put
(DoesFileExistQ -> Put)
-> Get DoesFileExistQ
-> ([DoesFileExistQ] -> Put)
-> Binary DoesFileExistQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [DoesFileExistQ] -> Put
$cputList :: [DoesFileExistQ] -> Put
get :: Get DoesFileExistQ
$cget :: Get DoesFileExistQ
put :: DoesFileExistQ -> Put
$cput :: DoesFileExistQ -> Put
Binary,ByteString -> DoesFileExistQ
DoesFileExistQ -> Builder
(DoesFileExistQ -> Builder)
-> (ByteString -> DoesFileExistQ) -> BinaryEx DoesFileExistQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> DoesFileExistQ
$cgetEx :: ByteString -> DoesFileExistQ
putEx :: DoesFileExistQ -> Builder
$cputEx :: DoesFileExistQ -> Builder
BinaryEx,DoesFileExistQ -> ()
(DoesFileExistQ -> ()) -> NFData DoesFileExistQ
forall a. (a -> ()) -> NFData a
rnf :: DoesFileExistQ -> ()
$crnf :: DoesFileExistQ -> ()
NFData)
instance Show DoesFileExistQ where
    show :: DoesFileExistQ -> String
show (DoesFileExistQ String
a) = String
"doesFileExist " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
a
newtype DoesFileExistA = DoesFileExistA {DoesFileExistA -> Bool
fromDoesFileExistA :: Bool}
    deriving (Typeable,DoesFileExistA -> DoesFileExistA -> Bool
(DoesFileExistA -> DoesFileExistA -> Bool)
-> (DoesFileExistA -> DoesFileExistA -> Bool) -> Eq DoesFileExistA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoesFileExistA -> DoesFileExistA -> Bool
$c/= :: DoesFileExistA -> DoesFileExistA -> Bool
== :: DoesFileExistA -> DoesFileExistA -> Bool
$c== :: DoesFileExistA -> DoesFileExistA -> Bool
Eq,ByteString -> DoesFileExistA
DoesFileExistA -> Builder
(DoesFileExistA -> Builder)
-> (ByteString -> DoesFileExistA) -> BinaryEx DoesFileExistA
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> DoesFileExistA
$cgetEx :: ByteString -> DoesFileExistA
putEx :: DoesFileExistA -> Builder
$cputEx :: DoesFileExistA -> Builder
BinaryEx,DoesFileExistA -> ()
(DoesFileExistA -> ()) -> NFData DoesFileExistA
forall a. (a -> ()) -> NFData a
rnf :: DoesFileExistA -> ()
$crnf :: DoesFileExistA -> ()
NFData)
instance Show DoesFileExistA where
    show :: DoesFileExistA -> String
show (DoesFileExistA Bool
a) = Bool -> String
forall a. Show a => a -> String
show Bool
a
type instance RuleResult DoesDirectoryExistQ = DoesDirectoryExistA
newtype DoesDirectoryExistQ = DoesDirectoryExistQ FilePath
    deriving (Typeable,DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool
(DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool)
-> (DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool)
-> Eq DoesDirectoryExistQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool
$c/= :: DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool
== :: DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool
$c== :: DoesDirectoryExistQ -> DoesDirectoryExistQ -> Bool
Eq,Int -> DoesDirectoryExistQ -> Int
DoesDirectoryExistQ -> Int
(Int -> DoesDirectoryExistQ -> Int)
-> (DoesDirectoryExistQ -> Int) -> Hashable DoesDirectoryExistQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DoesDirectoryExistQ -> Int
$chash :: DoesDirectoryExistQ -> Int
hashWithSalt :: Int -> DoesDirectoryExistQ -> Int
$chashWithSalt :: Int -> DoesDirectoryExistQ -> Int
Hashable,Get DoesDirectoryExistQ
[DoesDirectoryExistQ] -> Put
DoesDirectoryExistQ -> Put
(DoesDirectoryExistQ -> Put)
-> Get DoesDirectoryExistQ
-> ([DoesDirectoryExistQ] -> Put)
-> Binary DoesDirectoryExistQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [DoesDirectoryExistQ] -> Put
$cputList :: [DoesDirectoryExistQ] -> Put
get :: Get DoesDirectoryExistQ
$cget :: Get DoesDirectoryExistQ
put :: DoesDirectoryExistQ -> Put
$cput :: DoesDirectoryExistQ -> Put
Binary,ByteString -> DoesDirectoryExistQ
DoesDirectoryExistQ -> Builder
(DoesDirectoryExistQ -> Builder)
-> (ByteString -> DoesDirectoryExistQ)
-> BinaryEx DoesDirectoryExistQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> DoesDirectoryExistQ
$cgetEx :: ByteString -> DoesDirectoryExistQ
putEx :: DoesDirectoryExistQ -> Builder
$cputEx :: DoesDirectoryExistQ -> Builder
BinaryEx,DoesDirectoryExistQ -> ()
(DoesDirectoryExistQ -> ()) -> NFData DoesDirectoryExistQ
forall a. (a -> ()) -> NFData a
rnf :: DoesDirectoryExistQ -> ()
$crnf :: DoesDirectoryExistQ -> ()
NFData)
instance Show DoesDirectoryExistQ where
    show :: DoesDirectoryExistQ -> String
show (DoesDirectoryExistQ String
a) = String
"doesDirectoryExist " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
a
newtype DoesDirectoryExistA = DoesDirectoryExistA {DoesDirectoryExistA -> Bool
fromDoesDirectoryExistA :: Bool}
    deriving (Typeable,DoesDirectoryExistA -> DoesDirectoryExistA -> Bool
(DoesDirectoryExistA -> DoesDirectoryExistA -> Bool)
-> (DoesDirectoryExistA -> DoesDirectoryExistA -> Bool)
-> Eq DoesDirectoryExistA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoesDirectoryExistA -> DoesDirectoryExistA -> Bool
$c/= :: DoesDirectoryExistA -> DoesDirectoryExistA -> Bool
== :: DoesDirectoryExistA -> DoesDirectoryExistA -> Bool
$c== :: DoesDirectoryExistA -> DoesDirectoryExistA -> Bool
Eq,ByteString -> DoesDirectoryExistA
DoesDirectoryExistA -> Builder
(DoesDirectoryExistA -> Builder)
-> (ByteString -> DoesDirectoryExistA)
-> BinaryEx DoesDirectoryExistA
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> DoesDirectoryExistA
$cgetEx :: ByteString -> DoesDirectoryExistA
putEx :: DoesDirectoryExistA -> Builder
$cputEx :: DoesDirectoryExistA -> Builder
BinaryEx,DoesDirectoryExistA -> ()
(DoesDirectoryExistA -> ()) -> NFData DoesDirectoryExistA
forall a. (a -> ()) -> NFData a
rnf :: DoesDirectoryExistA -> ()
$crnf :: DoesDirectoryExistA -> ()
NFData)
instance Show DoesDirectoryExistA where
    show :: DoesDirectoryExistA -> String
show (DoesDirectoryExistA Bool
a) = Bool -> String
forall a. Show a => a -> String
show Bool
a
type instance RuleResult GetEnvQ = GetEnvA
newtype GetEnvQ = GetEnvQ String
    deriving (Typeable,GetEnvQ -> GetEnvQ -> Bool
(GetEnvQ -> GetEnvQ -> Bool)
-> (GetEnvQ -> GetEnvQ -> Bool) -> Eq GetEnvQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEnvQ -> GetEnvQ -> Bool
$c/= :: GetEnvQ -> GetEnvQ -> Bool
== :: GetEnvQ -> GetEnvQ -> Bool
$c== :: GetEnvQ -> GetEnvQ -> Bool
Eq,Int -> GetEnvQ -> Int
GetEnvQ -> Int
(Int -> GetEnvQ -> Int) -> (GetEnvQ -> Int) -> Hashable GetEnvQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetEnvQ -> Int
$chash :: GetEnvQ -> Int
hashWithSalt :: Int -> GetEnvQ -> Int
$chashWithSalt :: Int -> GetEnvQ -> Int
Hashable,Get GetEnvQ
[GetEnvQ] -> Put
GetEnvQ -> Put
(GetEnvQ -> Put)
-> Get GetEnvQ -> ([GetEnvQ] -> Put) -> Binary GetEnvQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [GetEnvQ] -> Put
$cputList :: [GetEnvQ] -> Put
get :: Get GetEnvQ
$cget :: Get GetEnvQ
put :: GetEnvQ -> Put
$cput :: GetEnvQ -> Put
Binary,ByteString -> GetEnvQ
GetEnvQ -> Builder
(GetEnvQ -> Builder) -> (ByteString -> GetEnvQ) -> BinaryEx GetEnvQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetEnvQ
$cgetEx :: ByteString -> GetEnvQ
putEx :: GetEnvQ -> Builder
$cputEx :: GetEnvQ -> Builder
BinaryEx,GetEnvQ -> ()
(GetEnvQ -> ()) -> NFData GetEnvQ
forall a. (a -> ()) -> NFData a
rnf :: GetEnvQ -> ()
$crnf :: GetEnvQ -> ()
NFData)
instance Show GetEnvQ where
    show :: GetEnvQ -> String
show (GetEnvQ String
a) = String
"getEnv " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
a
newtype GetEnvA = GetEnvA {GetEnvA -> Maybe String
fromGetEnvA :: Maybe String}
    deriving (Typeable,GetEnvA -> GetEnvA -> Bool
(GetEnvA -> GetEnvA -> Bool)
-> (GetEnvA -> GetEnvA -> Bool) -> Eq GetEnvA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEnvA -> GetEnvA -> Bool
$c/= :: GetEnvA -> GetEnvA -> Bool
== :: GetEnvA -> GetEnvA -> Bool
$c== :: GetEnvA -> GetEnvA -> Bool
Eq,Int -> GetEnvA -> Int
GetEnvA -> Int
(Int -> GetEnvA -> Int) -> (GetEnvA -> Int) -> Hashable GetEnvA
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetEnvA -> Int
$chash :: GetEnvA -> Int
hashWithSalt :: Int -> GetEnvA -> Int
$chashWithSalt :: Int -> GetEnvA -> Int
Hashable,ByteString -> GetEnvA
GetEnvA -> Builder
(GetEnvA -> Builder) -> (ByteString -> GetEnvA) -> BinaryEx GetEnvA
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetEnvA
$cgetEx :: ByteString -> GetEnvA
putEx :: GetEnvA -> Builder
$cputEx :: GetEnvA -> Builder
BinaryEx,GetEnvA -> ()
(GetEnvA -> ()) -> NFData GetEnvA
forall a. (a -> ()) -> NFData a
rnf :: GetEnvA -> ()
$crnf :: GetEnvA -> ()
NFData)
instance Show GetEnvA where
    show :: GetEnvA -> String
show (GetEnvA Maybe String
a) = String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"<unset>" ShowS
wrapQuote Maybe String
a
type instance RuleResult GetDirectoryContentsQ = GetDirectoryA
type instance RuleResult GetDirectoryFilesQ = GetDirectoryA
type instance RuleResult GetDirectoryDirsQ = GetDirectoryA
newtype GetDirectoryContentsQ = GetDirectoryContentsQ FilePath
    deriving (Typeable,GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool
(GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool)
-> (GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool)
-> Eq GetDirectoryContentsQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool
$c/= :: GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool
== :: GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool
$c== :: GetDirectoryContentsQ -> GetDirectoryContentsQ -> Bool
Eq,Int -> GetDirectoryContentsQ -> Int
GetDirectoryContentsQ -> Int
(Int -> GetDirectoryContentsQ -> Int)
-> (GetDirectoryContentsQ -> Int) -> Hashable GetDirectoryContentsQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetDirectoryContentsQ -> Int
$chash :: GetDirectoryContentsQ -> Int
hashWithSalt :: Int -> GetDirectoryContentsQ -> Int
$chashWithSalt :: Int -> GetDirectoryContentsQ -> Int
Hashable,Get GetDirectoryContentsQ
[GetDirectoryContentsQ] -> Put
GetDirectoryContentsQ -> Put
(GetDirectoryContentsQ -> Put)
-> Get GetDirectoryContentsQ
-> ([GetDirectoryContentsQ] -> Put)
-> Binary GetDirectoryContentsQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [GetDirectoryContentsQ] -> Put
$cputList :: [GetDirectoryContentsQ] -> Put
get :: Get GetDirectoryContentsQ
$cget :: Get GetDirectoryContentsQ
put :: GetDirectoryContentsQ -> Put
$cput :: GetDirectoryContentsQ -> Put
Binary,ByteString -> GetDirectoryContentsQ
GetDirectoryContentsQ -> Builder
(GetDirectoryContentsQ -> Builder)
-> (ByteString -> GetDirectoryContentsQ)
-> BinaryEx GetDirectoryContentsQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetDirectoryContentsQ
$cgetEx :: ByteString -> GetDirectoryContentsQ
putEx :: GetDirectoryContentsQ -> Builder
$cputEx :: GetDirectoryContentsQ -> Builder
BinaryEx,GetDirectoryContentsQ -> ()
(GetDirectoryContentsQ -> ()) -> NFData GetDirectoryContentsQ
forall a. (a -> ()) -> NFData a
rnf :: GetDirectoryContentsQ -> ()
$crnf :: GetDirectoryContentsQ -> ()
NFData)
instance Show GetDirectoryContentsQ where
    show :: GetDirectoryContentsQ -> String
show (GetDirectoryContentsQ String
dir) = String
"getDirectoryContents " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
dir
newtype GetDirectoryFilesQ = GetDirectoryFilesQ (FilePath, [FilePattern])
    deriving (Typeable,GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool
(GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool)
-> (GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool)
-> Eq GetDirectoryFilesQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool
$c/= :: GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool
== :: GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool
$c== :: GetDirectoryFilesQ -> GetDirectoryFilesQ -> Bool
Eq,Int -> GetDirectoryFilesQ -> Int
GetDirectoryFilesQ -> Int
(Int -> GetDirectoryFilesQ -> Int)
-> (GetDirectoryFilesQ -> Int) -> Hashable GetDirectoryFilesQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetDirectoryFilesQ -> Int
$chash :: GetDirectoryFilesQ -> Int
hashWithSalt :: Int -> GetDirectoryFilesQ -> Int
$chashWithSalt :: Int -> GetDirectoryFilesQ -> Int
Hashable,Get GetDirectoryFilesQ
[GetDirectoryFilesQ] -> Put
GetDirectoryFilesQ -> Put
(GetDirectoryFilesQ -> Put)
-> Get GetDirectoryFilesQ
-> ([GetDirectoryFilesQ] -> Put)
-> Binary GetDirectoryFilesQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [GetDirectoryFilesQ] -> Put
$cputList :: [GetDirectoryFilesQ] -> Put
get :: Get GetDirectoryFilesQ
$cget :: Get GetDirectoryFilesQ
put :: GetDirectoryFilesQ -> Put
$cput :: GetDirectoryFilesQ -> Put
Binary,ByteString -> GetDirectoryFilesQ
GetDirectoryFilesQ -> Builder
(GetDirectoryFilesQ -> Builder)
-> (ByteString -> GetDirectoryFilesQ)
-> BinaryEx GetDirectoryFilesQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetDirectoryFilesQ
$cgetEx :: ByteString -> GetDirectoryFilesQ
putEx :: GetDirectoryFilesQ -> Builder
$cputEx :: GetDirectoryFilesQ -> Builder
BinaryEx,GetDirectoryFilesQ -> ()
(GetDirectoryFilesQ -> ()) -> NFData GetDirectoryFilesQ
forall a. (a -> ()) -> NFData a
rnf :: GetDirectoryFilesQ -> ()
$crnf :: GetDirectoryFilesQ -> ()
NFData)
instance Show GetDirectoryFilesQ where
    show :: GetDirectoryFilesQ -> String
show (GetDirectoryFilesQ (String
dir, [String]
pat)) = String
"getDirectoryFiles " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
dir String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" [" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords (ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
wrapQuote [String]
pat) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"]"
newtype GetDirectoryDirsQ = GetDirectoryDirsQ FilePath
    deriving (Typeable,GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool
(GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool)
-> (GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool)
-> Eq GetDirectoryDirsQ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool
$c/= :: GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool
== :: GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool
$c== :: GetDirectoryDirsQ -> GetDirectoryDirsQ -> Bool
Eq,Int -> GetDirectoryDirsQ -> Int
GetDirectoryDirsQ -> Int
(Int -> GetDirectoryDirsQ -> Int)
-> (GetDirectoryDirsQ -> Int) -> Hashable GetDirectoryDirsQ
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetDirectoryDirsQ -> Int
$chash :: GetDirectoryDirsQ -> Int
hashWithSalt :: Int -> GetDirectoryDirsQ -> Int
$chashWithSalt :: Int -> GetDirectoryDirsQ -> Int
Hashable,Get GetDirectoryDirsQ
[GetDirectoryDirsQ] -> Put
GetDirectoryDirsQ -> Put
(GetDirectoryDirsQ -> Put)
-> Get GetDirectoryDirsQ
-> ([GetDirectoryDirsQ] -> Put)
-> Binary GetDirectoryDirsQ
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [GetDirectoryDirsQ] -> Put
$cputList :: [GetDirectoryDirsQ] -> Put
get :: Get GetDirectoryDirsQ
$cget :: Get GetDirectoryDirsQ
put :: GetDirectoryDirsQ -> Put
$cput :: GetDirectoryDirsQ -> Put
Binary,ByteString -> GetDirectoryDirsQ
GetDirectoryDirsQ -> Builder
(GetDirectoryDirsQ -> Builder)
-> (ByteString -> GetDirectoryDirsQ) -> BinaryEx GetDirectoryDirsQ
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetDirectoryDirsQ
$cgetEx :: ByteString -> GetDirectoryDirsQ
putEx :: GetDirectoryDirsQ -> Builder
$cputEx :: GetDirectoryDirsQ -> Builder
BinaryEx,GetDirectoryDirsQ -> ()
(GetDirectoryDirsQ -> ()) -> NFData GetDirectoryDirsQ
forall a. (a -> ()) -> NFData a
rnf :: GetDirectoryDirsQ -> ()
$crnf :: GetDirectoryDirsQ -> ()
NFData)
instance Show GetDirectoryDirsQ where
    show :: GetDirectoryDirsQ -> String
show (GetDirectoryDirsQ String
dir) = String
"getDirectoryDirs " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
wrapQuote String
dir
newtype GetDirectoryA = GetDirectoryA {GetDirectoryA -> [String]
fromGetDirectoryA :: [FilePath]}
    deriving (Typeable,GetDirectoryA -> GetDirectoryA -> Bool
(GetDirectoryA -> GetDirectoryA -> Bool)
-> (GetDirectoryA -> GetDirectoryA -> Bool) -> Eq GetDirectoryA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDirectoryA -> GetDirectoryA -> Bool
$c/= :: GetDirectoryA -> GetDirectoryA -> Bool
== :: GetDirectoryA -> GetDirectoryA -> Bool
$c== :: GetDirectoryA -> GetDirectoryA -> Bool
Eq,Int -> GetDirectoryA -> Int
GetDirectoryA -> Int
(Int -> GetDirectoryA -> Int)
-> (GetDirectoryA -> Int) -> Hashable GetDirectoryA
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetDirectoryA -> Int
$chash :: GetDirectoryA -> Int
hashWithSalt :: Int -> GetDirectoryA -> Int
$chashWithSalt :: Int -> GetDirectoryA -> Int
Hashable,ByteString -> GetDirectoryA
GetDirectoryA -> Builder
(GetDirectoryA -> Builder)
-> (ByteString -> GetDirectoryA) -> BinaryEx GetDirectoryA
forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a
getEx :: ByteString -> GetDirectoryA
$cgetEx :: ByteString -> GetDirectoryA
putEx :: GetDirectoryA -> Builder
$cputEx :: GetDirectoryA -> Builder
BinaryEx,GetDirectoryA -> ()
(GetDirectoryA -> ()) -> NFData GetDirectoryA
forall a. (a -> ()) -> NFData a
rnf :: GetDirectoryA -> ()
$crnf :: GetDirectoryA -> ()
NFData)
instance Show GetDirectoryA where
    show :: GetDirectoryA -> String
show (GetDirectoryA [String]
xs) = [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
wrapQuote [String]
xs
queryRule :: (RuleResult key ~ value
             ,BinaryEx witness, Eq witness
             ,BinaryEx key, ShakeValue key
             ,Typeable value, NFData value, Show value, Eq value)
          => (value -> witness) -> (key -> IO value) -> Rules ()
queryRule :: (value -> witness) -> (key -> IO value) -> Rules ()
queryRule value -> witness
witness key -> IO value
query = BuiltinLint key value
-> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
forall key value.
(RuleResult key ~ value, ShakeValue key, BinaryEx key,
 Typeable value, NFData value, Show value, Partial) =>
BuiltinLint key value
-> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRuleEx
    (\key
k value
old -> do
        value
new <- key -> IO value
query key
k
        Maybe String -> IO (Maybe String)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe String -> IO (Maybe String))
-> Maybe String -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ if value
old value -> value -> Bool
forall a. Eq a => a -> a -> Bool
== value
new then Maybe String
forall a. Maybe a
Nothing else String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ value -> String
forall a. Show a => a -> String
show value
new)
    (\key
_ value
v -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
runBuilder (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ witness -> Builder
forall a. BinaryEx a => a -> Builder
putEx (witness -> Builder) -> witness -> Builder
forall a b. (a -> b) -> a -> b
$ value -> witness
witness value
v)
    (\key
k Maybe ByteString
old RunMode
_ -> IO (RunResult value) -> Action (RunResult value)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (RunResult value) -> Action (RunResult value))
-> IO (RunResult value) -> Action (RunResult value)
forall a b. (a -> b) -> a -> b
$ do
        value
new <- key -> IO value
query key
k
        let wnew :: witness
wnew = value -> witness
witness value
new
        RunResult value -> IO (RunResult value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RunResult value -> IO (RunResult value))
-> RunResult value -> IO (RunResult value)
forall a b. (a -> b) -> a -> b
$ case Maybe ByteString
old of
            Just ByteString
old | witness
wnew witness -> witness -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString -> witness
forall a. BinaryEx a => ByteString -> a
getEx ByteString
old -> RunChanged -> ByteString -> value -> RunResult value
forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
ChangedNothing ByteString
old value
new
            Maybe ByteString
_ -> RunChanged -> ByteString -> value -> RunResult value
forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
ChangedRecomputeDiff (Builder -> ByteString
runBuilder (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ witness -> Builder
forall a. BinaryEx a => a -> Builder
putEx witness
wnew) value
new)
defaultRuleDirectory :: Rules ()
defaultRuleDirectory :: Rules ()
defaultRuleDirectory = do
    
    
    (DoesFileExistA -> DoesFileExistA)
-> (DoesFileExistQ -> IO DoesFileExistA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule DoesFileExistA -> DoesFileExistA
forall a. a -> a
id (\(DoesFileExistQ String
x) -> Bool -> DoesFileExistA
DoesFileExistA (Bool -> DoesFileExistA) -> IO Bool -> IO DoesFileExistA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
IO.doesFileExist String
x)
    (DoesDirectoryExistA -> DoesDirectoryExistA)
-> (DoesDirectoryExistQ -> IO DoesDirectoryExistA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule DoesDirectoryExistA -> DoesDirectoryExistA
forall a. a -> a
id (\(DoesDirectoryExistQ String
x) -> Bool -> DoesDirectoryExistA
DoesDirectoryExistA (Bool -> DoesDirectoryExistA) -> IO Bool -> IO DoesDirectoryExistA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
IO.doesDirectoryExist String
x)
    (GetEnvA -> Int) -> (GetEnvQ -> IO GetEnvA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule GetEnvA -> Int
forall a. Hashable a => a -> Int
hash (\(GetEnvQ String
x) -> Maybe String -> GetEnvA
GetEnvA (Maybe String -> GetEnvA) -> IO (Maybe String) -> IO GetEnvA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
IO.lookupEnv String
x)
    (GetDirectoryA -> Int)
-> (GetDirectoryContentsQ -> IO GetDirectoryA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule GetDirectoryA -> Int
forall a. Hashable a => a -> Int
hash (\(GetDirectoryContentsQ String
x) -> [String] -> GetDirectoryA
GetDirectoryA ([String] -> GetDirectoryA) -> IO [String] -> IO GetDirectoryA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO [String]
getDirectoryContentsIO String
x)
    (GetDirectoryA -> Int)
-> (GetDirectoryFilesQ -> IO GetDirectoryA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule GetDirectoryA -> Int
forall a. Hashable a => a -> Int
hash (\(GetDirectoryFilesQ (String
a,[String]
b)) -> [String] -> GetDirectoryA
GetDirectoryA ([String] -> GetDirectoryA) -> IO [String] -> IO GetDirectoryA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String] -> IO [String]
getDirectoryFilesIO String
a [String]
b)
    (GetDirectoryA -> Int)
-> (GetDirectoryDirsQ -> IO GetDirectoryA) -> Rules ()
forall key value witness.
(RuleResult key ~ value, BinaryEx witness, Eq witness,
 BinaryEx key, ShakeValue key, Typeable value, NFData value,
 Show value, Eq value) =>
(value -> witness) -> (key -> IO value) -> Rules ()
queryRule GetDirectoryA -> Int
forall a. Hashable a => a -> Int
hash (\(GetDirectoryDirsQ String
x) -> [String] -> GetDirectoryA
GetDirectoryA ([String] -> GetDirectoryA) -> IO [String] -> IO GetDirectoryA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO [String]
getDirectoryDirsIO String
x)
doesFileExist :: FilePath -> Action Bool
doesFileExist :: String -> Action Bool
doesFileExist = (DoesFileExistA -> Bool) -> Action DoesFileExistA -> Action Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DoesFileExistA -> Bool
fromDoesFileExistA (Action DoesFileExistA -> Action Bool)
-> (String -> Action DoesFileExistA) -> String -> Action Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoesFileExistQ -> Action DoesFileExistA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (DoesFileExistQ -> Action DoesFileExistA)
-> (String -> DoesFileExistQ) -> String -> Action DoesFileExistA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> DoesFileExistQ
DoesFileExistQ (String -> DoesFileExistQ) -> ShowS -> String -> DoesFileExistQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
toStandard
doesDirectoryExist :: FilePath -> Action Bool
doesDirectoryExist :: String -> Action Bool
doesDirectoryExist = (DoesDirectoryExistA -> Bool)
-> Action DoesDirectoryExistA -> Action Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DoesDirectoryExistA -> Bool
fromDoesDirectoryExistA (Action DoesDirectoryExistA -> Action Bool)
-> (String -> Action DoesDirectoryExistA) -> String -> Action Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoesDirectoryExistQ -> Action DoesDirectoryExistA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (DoesDirectoryExistQ -> Action DoesDirectoryExistA)
-> (String -> DoesDirectoryExistQ)
-> String
-> Action DoesDirectoryExistA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> DoesDirectoryExistQ
DoesDirectoryExistQ (String -> DoesDirectoryExistQ)
-> ShowS -> String -> DoesDirectoryExistQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
toStandard
getEnv :: String -> Action (Maybe String)
getEnv :: String -> Action (Maybe String)
getEnv = (GetEnvA -> Maybe String)
-> Action GetEnvA -> Action (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GetEnvA -> Maybe String
fromGetEnvA (Action GetEnvA -> Action (Maybe String))
-> (String -> Action GetEnvA) -> String -> Action (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetEnvQ -> Action GetEnvA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (GetEnvQ -> Action GetEnvA)
-> (String -> GetEnvQ) -> String -> Action GetEnvA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GetEnvQ
GetEnvQ
getEnvWithDefault :: String -> String -> Action String
getEnvWithDefault :: String -> String -> Action String
getEnvWithDefault String
def String
var = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
def (Maybe String -> String) -> Action (Maybe String) -> Action String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Action (Maybe String)
getEnv String
var
getEnvError :: Partial => String -> Action String
getEnvError :: String -> Action String
getEnvError String
name = String -> String -> Action String
getEnvWithDefault (ShowS
forall a. Partial => String -> a
error ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
"getEnvError: Environment variable " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is undefined") String
name
getDirectoryContents :: FilePath -> Action [FilePath]
getDirectoryContents :: String -> Action [String]
getDirectoryContents = (GetDirectoryA -> [String])
-> Action GetDirectoryA -> Action [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GetDirectoryA -> [String]
fromGetDirectoryA (Action GetDirectoryA -> Action [String])
-> (String -> Action GetDirectoryA) -> String -> Action [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetDirectoryContentsQ -> Action GetDirectoryA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (GetDirectoryContentsQ -> Action GetDirectoryA)
-> (String -> GetDirectoryContentsQ)
-> String
-> Action GetDirectoryA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GetDirectoryContentsQ
GetDirectoryContentsQ
getDirectoryFiles :: FilePath -> [FilePattern] -> Action [FilePath]
getDirectoryFiles :: String -> [String] -> Action [String]
getDirectoryFiles String
dir [String]
pat = (GetDirectoryA -> [String])
-> Action GetDirectoryA -> Action [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GetDirectoryA -> [String]
fromGetDirectoryA (Action GetDirectoryA -> Action [String])
-> Action GetDirectoryA -> Action [String]
forall a b. (a -> b) -> a -> b
$ GetDirectoryFilesQ -> Action GetDirectoryA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (GetDirectoryFilesQ -> Action GetDirectoryA)
-> GetDirectoryFilesQ -> Action GetDirectoryA
forall a b. (a -> b) -> a -> b
$ (String, [String]) -> GetDirectoryFilesQ
GetDirectoryFilesQ (String
dir,[String]
pat)
getDirectoryDirs :: FilePath -> Action [FilePath]
getDirectoryDirs :: String -> Action [String]
getDirectoryDirs = (GetDirectoryA -> [String])
-> Action GetDirectoryA -> Action [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GetDirectoryA -> [String]
fromGetDirectoryA (Action GetDirectoryA -> Action [String])
-> (String -> Action GetDirectoryA) -> String -> Action [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GetDirectoryDirsQ -> Action GetDirectoryA
forall key value.
(Partial, RuleResult key ~ value, ShakeValue key,
 Typeable value) =>
key -> Action value
apply1 (GetDirectoryDirsQ -> Action GetDirectoryA)
-> (String -> GetDirectoryDirsQ) -> String -> Action GetDirectoryA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GetDirectoryDirsQ
GetDirectoryDirsQ
getDirectoryContentsIO :: FilePath -> IO [FilePath]
getDirectoryContentsIO :: String -> IO [String]
getDirectoryContentsIO String
dir = ([String] -> [String]) -> IO [String] -> IO [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'))) (IO [String] -> IO [String]) -> IO [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ String -> IO [String]
IO.getDirectoryContents (String -> IO [String]) -> String -> IO [String]
forall a b. (a -> b) -> a -> b
$ if String
dir String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"" then String
"." else String
dir
getDirectoryDirsIO :: FilePath -> IO [FilePath]
getDirectoryDirsIO :: String -> IO [String]
getDirectoryDirsIO String
dir = (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM String -> IO Bool
f ([String] -> IO [String]) -> IO [String] -> IO [String]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
getDirectoryContentsIO String
dir
    where f :: String -> IO Bool
f String
x = String -> IO Bool
IO.doesDirectoryExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
dir String -> ShowS
</> String
x
getDirectoryFilesIO :: FilePath -> [FilePattern] -> IO [FilePath]
getDirectoryFilesIO :: String -> [String] -> IO [String]
getDirectoryFilesIO String
root [String]
pat = String -> Walk -> IO [String]
f String
"" (Walk -> IO [String]) -> Walk -> IO [String]
forall a b. (a -> b) -> a -> b
$ (Bool, Walk) -> Walk
forall a b. (a, b) -> b
snd ((Bool, Walk) -> Walk) -> (Bool, Walk) -> Walk
forall a b. (a -> b) -> a -> b
$ [String] -> (Bool, Walk)
walk [String]
pat
    where
        
        
        f :: String -> Walk -> IO [String]
f String
dir (Walk [String] -> ([String], [(String, Walk)])
op) = String -> Walk -> IO [String]
f String
dir (Walk -> IO [String])
-> ([String] -> Walk) -> [String] -> IO [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String], [(String, Walk)]) -> Walk
WalkTo (([String], [(String, Walk)]) -> Walk)
-> ([String] -> ([String], [(String, Walk)])) -> [String] -> Walk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> ([String], [(String, Walk)])
op ([String] -> IO [String]) -> IO [String] -> IO [String]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
getDirectoryContentsIO (String
root String -> ShowS
</> String
dir)
        f String
dir (WalkTo ([String]
files, [(String, Walk)]
dirs)) = do
            [String]
files <- (String -> IO Bool) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesFileExist (String -> IO Bool) -> ShowS -> String -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
root String -> ShowS
</>)) ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
dir String -> ShowS
</>) [String]
files
            [String]
dirs <- ((String, Walk) -> IO [String]) -> [(String, Walk)] -> IO [String]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM ((String -> Walk -> IO [String]) -> (String, Walk) -> IO [String]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> Walk -> IO [String]
f) ([(String, Walk)] -> IO [String])
-> IO [(String, Walk)] -> IO [String]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ((String, Walk) -> IO Bool)
-> [(String, Walk)] -> IO [(String, Walk)]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesDirectoryExist (String -> IO Bool)
-> ((String, Walk) -> String) -> (String, Walk) -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
root String -> ShowS
</>) ShowS -> ((String, Walk) -> String) -> (String, Walk) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Walk) -> String
forall a b. (a, b) -> a
fst) (((String, Walk) -> (String, Walk))
-> [(String, Walk)] -> [(String, Walk)]
forall a b. (a -> b) -> [a] -> [b]
map (ShowS -> (String, Walk) -> (String, Walk)
forall a a' b. (a -> a') -> (a, b) -> (a', b)
first (String
dir String -> ShowS
</>)) [(String, Walk)]
dirs)
            [String] -> IO [String]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([String] -> IO [String]) -> [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ [String]
files [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
dirs
removeFiles :: FilePath -> [FilePattern] -> IO ()
removeFiles :: String -> [String] -> IO ()
removeFiles String
dir [String]
pat =
    IO Bool -> IO () -> IO ()
forall (m :: * -> *). Monad m => m Bool -> m () -> m ()
whenM (String -> IO Bool
IO.doesDirectoryExist String
dir) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        let (Bool
b,Walk
w) = [String] -> (Bool, Walk)
walk [String]
pat
        if Bool
b then String -> IO ()
removeDir String
dir else String -> Walk -> IO ()
f String
dir Walk
w
    where
        f :: String -> Walk -> IO ()
f String
dir (Walk [String] -> ([String], [(String, Walk)])
op) = String -> Walk -> IO ()
f String
dir (Walk -> IO ()) -> ([String] -> Walk) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String], [(String, Walk)]) -> Walk
WalkTo (([String], [(String, Walk)]) -> Walk)
-> ([String] -> ([String], [(String, Walk)])) -> [String] -> Walk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> ([String], [(String, Walk)])
op ([String] -> IO ()) -> IO [String] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
getDirectoryContentsIO String
dir
        f String
dir (WalkTo ([String]
files, [(String, Walk)]
dirs)) = do
            [String] -> (String -> IO (Either IOException ())) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
files ((String -> IO (Either IOException ())) -> IO ())
-> (String -> IO (Either IOException ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
fil ->
                IO () -> IO (Either IOException ())
forall a. IO a -> IO (Either IOException a)
tryIO (IO () -> IO (Either IOException ()))
-> IO () -> IO (Either IOException ())
forall a b. (a -> b) -> a -> b
$ String -> IO ()
removeItem (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
dir String -> ShowS
</> String
fil
            let done :: HashSet String
done = [String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList [String]
files
            [(String, Walk)] -> ((String, Walk) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (((String, Walk) -> Bool) -> [(String, Walk)] -> [(String, Walk)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((String, Walk) -> Bool) -> (String, Walk) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> HashSet String -> Bool)
-> HashSet String -> String -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> HashSet String -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
Set.member HashSet String
done (String -> Bool)
-> ((String, Walk) -> String) -> (String, Walk) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Walk) -> String
forall a b. (a, b) -> a
fst) [(String, Walk)]
dirs) (((String, Walk) -> IO ()) -> IO ())
-> ((String, Walk) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(String
d,Walk
w) -> do
                let dir2 :: String
dir2 = String
dir String -> ShowS
</> String
d
                IO Bool -> IO () -> IO ()
forall (m :: * -> *). Monad m => m Bool -> m () -> m ()
whenM (String -> IO Bool
IO.doesDirectoryExist String
dir2) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Walk -> IO ()
f String
dir2 Walk
w
        removeItem :: FilePath -> IO ()
        removeItem :: String -> IO ()
removeItem String
x = String -> IO ()
IO.removeFile String
x IO () -> (IOException -> IO ()) -> IO ()
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` \IOException
_ -> String -> IO ()
removeDir String
x
        
        
        removeDir :: FilePath -> IO ()
        removeDir :: String -> IO ()
removeDir String
x = do
            (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String -> IO ()
removeItem (String -> IO ()) -> ShowS -> String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
x String -> ShowS
</>)) ([String] -> IO ()) -> IO [String] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IO [String]
getDirectoryContentsIO String
x
            String -> IO ()
IO.removeDirectory String
x
removeFilesAfter :: FilePath -> [FilePattern] -> Action ()
removeFilesAfter :: String -> [String] -> Action ()
removeFilesAfter String
a [String]
b = do
    String -> Action ()
putVerbose (String -> Action ()) -> String -> Action ()
forall a b. (a -> b) -> a -> b
$ String
"Will remove " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
b String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" from " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
a
    IO () -> Action ()
runAfter (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO ()
removeFiles String
a [String]
b