{-# LANGUAGE ScopedTypeVariables, DeriveDataTypeable, OverloadedStrings,
FlexibleInstances, IncoherentInstances,
TypeFamilies, ExistentialQuantification #-}
module Shelly
(
Sh, ShIO, shelly, shellyNoDir, shellyFailDir, asyncSh, sub
, silently, verbosely, escaping, print_stdout, print_stderr, print_commands
, onCommandHandles
, tracing, errExit
, log_stdout_with, log_stderr_with
, run, run_, runFoldLines, cmd, FoldCallback
, bash, bash_, bashPipeFail
, (-|-), lastStderr, setStdin, lastExitCode
, command, command_, command1, command1_
, sshPairs,sshPairsPar, sshPairs_,sshPairsPar_, sshPairsWithOptions
, sshCommandText, SshMode(..)
, ShellCmd(..), CmdArg (..)
, runHandle, runHandles, transferLinesAndCombine, transferFoldHandleLines
, StdHandle(..), StdStream(..)
, HandleInitializer, StdInit(..), initOutputHandles, initAllHandles
, setenv, get_env, get_env_text, getenv, get_env_def, get_env_all, get_environment, appendToPath, prependToPath
, cd, chdir, chdir_p, pwd
, echo, echo_n, echo_err, echo_n_err, inspect, inspect_err
, tag, trace, show_command
, ls, lsT, test_e, test_f, test_d, test_s, test_px, which
, absPath, (</>), (<.>), canonic, canonicalize, relPath, relativeTo, path
, hasExt
, mv, rm, rm_f, rm_rf, cp, cp_r, mkdir, mkdir_p, mkdirTree
, readfile, readBinary, writefile, writeBinary, appendfile, touchfile, withTmpDir
, exit, errorExit, quietExit, terror
, bracket_sh, catchany, catch_sh, handle_sh, handleany_sh, finally_sh, ShellyHandler(..), catches_sh, catchany_sh
, ReThrownException(..)
, RunFailed(..)
, toTextIgnore, toTextWarn, fromText
, whenM, unlessM, time, sleep
, liftIO, when, unless, FilePath, (<$>)
, get, put
, find, findWhen, findFold, findDirFilter, findDirFilterWhen, findFoldDirFilter
, followSymlink
) where
import Shelly.Base
import Shelly.Directory
import Shelly.Find
import Control.Monad ( when, unless, void, forM, filterM, liftM2 )
import Control.Monad.Trans ( MonadIO )
import Control.Monad.Reader (ask)
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 706
import Prelude hiding ( readFile, FilePath, catch)
#else
import Prelude hiding ( readFile, FilePath)
#endif
import Data.Char ( isAlphaNum, isSpace, toLower )
import Data.Typeable
import Data.IORef
import Data.Sequence (Seq, (|>))
import Data.Foldable (toList)
import Data.Maybe
import System.IO ( hClose, stderr, stdout, openTempFile)
import System.IO.Error (isPermissionError, catchIOError, isEOFError, isIllegalOperation)
import System.Exit
import System.Environment
import Control.Applicative
import Control.Exception
import Control.Concurrent
import Control.Concurrent.Async (async, wait, Async)
import Data.Time.Clock( getCurrentTime, diffUTCTime )
import qualified Data.Text.IO as TIO
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TE
import System.Process( CmdSpec(..), StdStream(CreatePipe, UseHandle), CreateProcess(..), createProcess, waitForProcess, terminateProcess, ProcessHandle, StdStream(..) )
import qualified Data.Text as T
import qualified Data.ByteString as BS
import Data.ByteString (ByteString)
import Data.Monoid (Monoid, mempty, mappend)
#if __GLASGOW_HASKELL__ < 704
infixr 5 <>
(<>) :: Monoid m => m -> m -> m
(<>) = mappend
#else
import Data.Monoid ((<>))
#endif
import System.FilePath hiding ((</>), (<.>))
import qualified System.FilePath as FP
import System.Directory ( setPermissions, getPermissions, Permissions(..), getTemporaryDirectory, pathIsSymbolicLink
, copyFile, removeFile, doesFileExist, doesDirectoryExist, listDirectory
, renameFile, renameDirectory, removeDirectoryRecursive, createDirectoryIfMissing
, getCurrentDirectory )
import System.IO (Handle)
import Data.Char (isDigit)
import Data.Tree(Tree(..))
import qualified Data.Set as S
import qualified Data.List as L
class CmdArg a where toTextArg :: a -> Text
instance CmdArg Text where toTextArg = id
instance CmdArg String where toTextArg = T.pack
class ShellCmd t where
cmdAll :: FilePath -> [Text] -> t
instance ShellCmd (Sh Text) where
cmdAll = run
instance (s ~ Text, Show s) => ShellCmd (Sh s) where
cmdAll = run
instance ShellCmd (Sh ()) where
cmdAll = run_
instance (CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) where
cmdAll fp acc x = cmdAll fp (acc ++ [toTextArg x])
instance (CmdArg arg, ShellCmd result) => ShellCmd ([arg] -> result) where
cmdAll fp acc x = cmdAll fp (acc ++ map toTextArg x)
cmd :: (ShellCmd result) => FilePath -> result
cmd fp = cmdAll fp []
fromText :: Text -> FilePath
fromText = T.unpack
class ToFilePath a where
toFilePath :: a -> FilePath
instance ToFilePath FilePath where toFilePath = id
instance ToFilePath Text where toFilePath = T.unpack
(</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath
x </> y = toFilePath x FP.</> toFilePath y
(<.>) :: (ToFilePath filepath) => filepath -> Text -> FilePath
x <.> y = toFilePath x FP.<.> T.unpack y
toTextWarn :: FilePath -> Sh Text
toTextWarn efile = do
when (not $ isValid efile) $ encodeError (T.pack $ makeValid efile)
return (T.pack $ makeValid efile)
where
encodeError f = echo ("non-unicode file name: " <> f)
transferLinesAndCombine :: Handle -> (Text -> IO ()) -> IO Text
transferLinesAndCombine readHandle putWrite =
transferFoldHandleLines mempty (|>) readHandle putWrite >>=
return . lineSeqToText
lineSeqToText :: Seq Text -> Text
lineSeqToText = T.intercalate "\n" . toList . flip (|>) ""
type FoldCallback a = (a -> Text -> a)
transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a
transferFoldHandleLines start foldLine readHandle putWrite = go start
where
go acc = do
mLine <- filterIOErrors $ TIO.hGetLine readHandle
case mLine of
Nothing -> return acc
Just line -> putWrite line >> go (foldLine acc line)
filterIOErrors :: IO a -> IO (Maybe a)
filterIOErrors action = catchIOError
(fmap Just action)
(\e -> if isEOFError e || isIllegalOperation e
then return Nothing
else ioError e)
foldHandleLines :: a -> FoldCallback a -> Handle -> IO a
foldHandleLines start foldLine readHandle = go start
where
go acc = do
mLine <- filterIOErrors $ TIO.hGetLine readHandle
case mLine of
Nothing -> return acc
Just line -> go $ foldLine acc line
tag :: Sh a -> Text -> Sh a
tag action msg = do
trace msg
action
put :: State -> Sh ()
put newState = do
stateVar <- ask
liftIO (writeIORef stateVar newState)
runCommandNoEscape :: [StdHandle] -> State -> FilePath -> [Text] -> Sh (Handle, Handle, Handle, ProcessHandle)
runCommandNoEscape handles st exe args = liftIO $ shellyProcess handles st $
ShellCommand $ T.unpack $ T.intercalate " " (toTextIgnore exe : args)
runCommand :: [StdHandle] -> State -> FilePath -> [Text] -> Sh (Handle, Handle, Handle, ProcessHandle)
runCommand handles st exe args = findExe exe >>= \fullExe ->
liftIO $ shellyProcess handles st $
RawCommand fullExe (map T.unpack args)
where
findExe :: FilePath -> Sh FilePath
findExe
#if defined(mingw32_HOST_OS) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 708)
fp
#else
_fp
#endif
= do
mExe <- whichEith exe
case mExe of
Right execFp -> return execFp
#if defined(mingw32_HOST_OS) || (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ < 708)
Left _ -> return fp
#else
Left err -> liftIO $ throwIO $ userError err
#endif
shellyProcess :: [StdHandle] -> State -> CmdSpec -> IO (Handle, Handle, Handle, ProcessHandle)
shellyProcess reusedHandles st cmdSpec = do
(createdInH, createdOutH, createdErrorH, pHandle) <- createProcess CreateProcess {
cmdspec = cmdSpec
, cwd = Just $ sDirectory st
, env = Just $ sEnvironment st
, std_in = createUnless mInH
, std_out = createUnless mOutH
, std_err = createUnless mErrorH
, close_fds = False
#if MIN_VERSION_process(1,1,0)
, create_group = False
#endif
#if MIN_VERSION_process(1,2,0)
, delegate_ctlc = False
#endif
#if MIN_VERSION_process(1,3,0)
, detach_console = False
, create_new_console = False
, new_session = False
#endif
#if MIN_VERSION_process(1,4,0)
, child_group = Nothing
, child_user = Nothing
#endif
#if MIN_VERSION_process(1,5,0)
, use_process_jobs = False
#endif
}
return ( just $ createdInH <|> toHandle mInH
, just $ createdOutH <|> toHandle mOutH
, just $ createdErrorH <|> toHandle mErrorH
, pHandle
)
where
just :: Maybe a -> a
just Nothing = error "error in shelly creating process"
just (Just j) = j
toHandle (Just (UseHandle h)) = Just h
toHandle (Just CreatePipe) = error "shelly process creation failure CreatePipe"
toHandle (Just Inherit) = error "cannot access an inherited pipe"
toHandle Nothing = error "error in shelly creating process"
createUnless Nothing = CreatePipe
createUnless (Just stream) = stream
mInH = getStream mIn reusedHandles
mOutH = getStream mOut reusedHandles
mErrorH = getStream mError reusedHandles
getStream :: (StdHandle -> Maybe StdStream) -> [StdHandle] -> Maybe StdStream
getStream _ [] = Nothing
getStream mHandle (h:hs) = mHandle h <|> getStream mHandle hs
mIn, mOut, mError :: (StdHandle -> Maybe StdStream)
mIn (InHandle h) = Just h
mIn _ = Nothing
mOut (OutHandle h) = Just h
mOut _ = Nothing
mError (ErrorHandle h) = Just h
mError _ = Nothing
{-
-- | use for commands requiring usage of sudo. see 'run_sudo'.
-- Use this pattern for priveledge separation
newtype Sudo a = Sudo { sudo :: Sh a }
-- | require that the caller explicitly state 'sudo'
run_sudo :: Text -> [Text] -> Sudo Text
run_sudo cmd args = Sudo $ run "/usr/bin/sudo" (cmd:args)
-}
-- | Same as a normal 'catch' but specialized for the Sh monad.
catch_sh :: (Exception e) => Sh a -> (e -> Sh a) -> Sh a
catch_sh action handler = do
ref <- ask
liftIO $ catch (runSh action ref) (\e -> runSh (handler e) ref)
-- | Same as a normal 'handle' but specialized for the Sh monad.
handle_sh :: (Exception e) => (e -> Sh a) -> Sh a -> Sh a
handle_sh handler action = do
ref <- ask
liftIO $ handle (\e -> runSh (handler e) ref) (runSh action ref)
-- | Same as a normal 'finally' but specialized for the 'Sh' monad.
finally_sh :: Sh a -> Sh b -> Sh a
finally_sh action handler = do
ref <- ask
liftIO $ finally (runSh action ref) (runSh handler ref)
bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh c
bracket_sh acquire release main = do
ref <- ask
liftIO $ bracket (runSh acquire ref)
(\resource -> runSh (release resource) ref)
(\resource -> runSh (main resource) ref)
-- | You need to wrap exception handlers with this when using 'catches_sh'.
data ShellyHandler a = forall e . Exception e => ShellyHandler (e -> Sh a)
-- | Same as a normal 'catches', but specialized for the 'Sh' monad.
catches_sh :: Sh a -> [ShellyHandler a] -> Sh a
catches_sh action handlers = do
ref <- ask
let runner a = runSh a ref
liftIO $ catches (runner action) $ map (toHandler runner) handlers
where
toHandler :: (Sh a -> IO a) -> ShellyHandler a -> Handler a
toHandler runner (ShellyHandler handler) = Handler (\e -> runner (handler e))
-- | Catch any exception in the Sh monad.
catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a
catchany_sh = catch_sh
-- | Handle any exception in the Sh monad.
handleany_sh :: (SomeException -> Sh a) -> Sh a -> Sh a
handleany_sh = handle_sh
-- | Change current working directory of Sh. This does *not* change the
-- working directory of the process we are running it. Instead, Sh keeps
-- track of its own working directory and builds absolute paths internally
-- instead of passing down relative paths.
cd :: FilePath -> Sh ()
cd = traceCanonicPath ("cd " <>) >=> cd'
where
cd' dir = do
unlessM (test_d dir) $ errorExit $ "not a directory: " <> tdir
modify $ \st -> st { sDirectory = dir, sPathExecutables = Nothing }
where
tdir = toTextIgnore dir
-- | 'cd', execute a Sh action in the new directory and then pop back to the original directory
chdir :: FilePath -> Sh a -> Sh a
chdir dir action = do
d <- gets sDirectory
cd dir
action `finally_sh` cd d
-- | 'chdir', but first create the directory if it does not exit
chdir_p :: FilePath -> Sh a -> Sh a
chdir_p d action = mkdir_p d >> chdir d action
-- | apply a String IO operations to a Text FilePath
{-
liftStringIO :: (String -> IO String) -> FilePath -> Sh FilePath
liftStringIO f = liftIO . f . unpack >=> return . pack
-- | @asString f = pack . f . unpack@
asString :: (String -> String) -> FilePath -> FilePath
asString f = pack . f . unpack
-}
pack :: String -> FilePath
pack = id
-- | Move a file. The second path could be a directory, in which case the
-- original file is moved into that directory.
-- wraps directory 'System.Directory.renameFile', which may not work across FS boundaries
mv :: FilePath -> FilePath -> Sh ()
mv from' to' = do
trace $ "mv " <> toTextIgnore from' <> " " <> toTextIgnore to'
from <- absPath from'
from_dir <- test_d from
to <- absPath to'
to_dir <- test_d to
let to_loc = if not to_dir then to else to FP.</> (FP.takeFileName from)
liftIO $ createDirectoryIfMissing True (takeDirectory to_loc)
if not from_dir
then liftIO $ renameFile from to_loc
`catchany` (\e -> throwIO $
ReThrownException e (extraMsg to_loc from)
)
else liftIO $ renameDirectory from to_loc
`catchany` (\e -> throwIO $
ReThrownException e (extraMsg to_loc from)
)
where
extraMsg :: String -> String -> String
extraMsg t f = "during copy from: " ++ f ++ " to: " ++ t
-- | Get back [Text] instead of [FilePath]
lsT :: FilePath -> Sh [Text]
lsT = ls >=> mapM toTextWarn
-- | Obtain the current (Sh) working directory.
pwd :: Sh FilePath
pwd = gets sDirectory `tag` "pwd"
-- | exit 0 means no errors, all other codes are error conditions
exit :: Int -> Sh a
exit 0 = liftIO exitSuccess `tag` "exit 0"
exit n = liftIO (exitWith (ExitFailure n)) `tag` ("exit " <> T.pack (show n))
-- | echo a message and exit with status 1
errorExit :: Text -> Sh a
errorExit msg = echo msg >> exit 1
-- | for exiting with status > 0 without printing debug information
quietExit :: Int -> Sh a
quietExit 0 = exit 0
quietExit n = throw $ QuietExit n
-- | fail that takes a Text
terror :: Text -> Sh a
terror = fail . T.unpack
-- | Create a new directory (fails if the directory exists).
mkdir :: FilePath -> Sh ()
mkdir = traceAbsPath ("mkdir " <>) >=>
liftIO . createDirectoryIfMissing False
-- | Create a new directory, including parents (succeeds if the directory
-- already exists).
mkdir_p :: FilePath -> Sh ()
mkdir_p = traceAbsPath ("mkdir -p " <>) >=>
liftIO . createDirectoryIfMissing True
-- | Create a new directory tree. You can describe a bunch of directories as
-- a tree and this function will create all subdirectories. An example:
--
-- > exec = mkTree $
-- > "package" # [
-- > "src" # [
-- > "Data" # leaves ["Tree", "List", "Set", "Map"]
-- > ],
-- > "test" # leaves ["QuickCheck", "HUnit"],
-- > "dist/doc/html" # []
-- > ]
-- > where (#) = Node
-- > leaves = map (# [])
--
mkdirTree :: Tree FilePath -> Sh ()
mkdirTree = mk . unrollPath
where mk :: Tree FilePath -> Sh ()
mk (Node a ts) = do
b <- test_d a
unless b $ mkdir a
chdir a $ mapM_ mkdirTree ts
unrollPath :: Tree FilePath -> Tree FilePath
unrollPath (Node v ts) = unrollRoot v $ map unrollPath ts
where unrollRoot x = foldr1 phi $ map Node $ splitDirectories x
phi a b = a . return . b
isExecutable :: FilePath -> IO Bool
isExecutable f = (executable `fmap` getPermissions f) `catch` (\(_ :: IOError) -> return False)
-- | Get a full path to an executable by looking at the @PATH@ environement
-- variable. Windows normally looks in additional places besides the
-- @PATH@: this does not duplicate that behavior.
which :: FilePath -> Sh (Maybe FilePath)
which fp = either (const Nothing) Just <$> whichEith fp
-- | Get a full path to an executable by looking at the @PATH@ environement
-- variable. Windows normally looks in additional places besides the
-- @PATH@: this does not duplicate that behavior.
whichEith :: FilePath -> Sh (Either String FilePath)
whichEith originalFp = whichFull
#if defined(mingw32_HOST_OS)
$ case extension originalFp of
Nothing -> originalFp <.> "exe"
Just _ -> originalFp
#else
originalFp
#endif
where
whichFull fp = do
(trace . mappend "which " . toTextIgnore) fp >> whichUntraced
where
whichUntraced | isAbsolute fp = checkFile
| dotSlash splitOnDirs = checkFile
| length splitOnDirs > 0 = lookupPath >>= leftPathError
| otherwise = lookupCache >>= leftPathError
splitOnDirs = splitDirectories fp
dotSlash ("./":_) = True
dotSlash _ = False
checkFile :: Sh (Either String FilePath)
checkFile = do
exists <- liftIO $ doesFileExist fp
return $ if exists then Right fp else
Left $ "did not find file: " <> fp
leftPathError :: Maybe FilePath -> Sh (Either String FilePath)
leftPathError Nothing = Left <$> pathLookupError
leftPathError (Just x) = return $ Right x
pathLookupError :: Sh String
pathLookupError = do
pATH <- get_env_text "PATH"
return $
"shelly did not find " `mappend` fp `mappend`
" in the PATH: " `mappend` T.unpack pATH
lookupPath :: Sh (Maybe FilePath)
lookupPath = (pathDirs >>=) $ findMapM $ \dir -> do
let fullFp = dir </> fp
res <- liftIO $ isExecutable fullFp
return $ if res then Just fullFp else Nothing
lookupCache :: Sh (Maybe FilePath)
lookupCache = do
pathExecutables <- cachedPathExecutables
return $ fmap (flip (</>) fp . fst) $
L.find (S.member fp . snd) pathExecutables
pathDirs = mapM absPath =<< ((map T.unpack . filter (not . T.null) . T.split (== searchPathSeparator)) `fmap` get_env_text "PATH")
cachedPathExecutables :: Sh [(FilePath, S.Set FilePath)]
cachedPathExecutables = do
mPathExecutables <- gets sPathExecutables
case mPathExecutables of
Just pExecutables -> return pExecutables
Nothing -> do
dirs <- pathDirs
executables <- forM dirs (\dir -> do
files <- (liftIO . listDirectory) dir `catch_sh` (\(_ :: IOError) -> return [])
exes <- fmap (map snd) $ liftIO $ filterM (isExecutable . fst) $
map (\f -> (f, takeFileName f)) files
return $ S.fromList exes
)
let cachedExecutables = zip dirs executables
modify $ \x -> x { sPathExecutables = Just cachedExecutables }
return $ cachedExecutables
findMapM :: Monad m => (a -> m (Maybe b)) -> [a] -> m (Maybe b)
findMapM _ [] = return Nothing
findMapM f (x:xs) = do
mb <- f x
if (isJust mb)
then return mb
else findMapM f xs
unlessM :: Monad m => m Bool -> m () -> m ()
unlessM c a = c >>= \res -> unless res a
test_e :: FilePath -> Sh Bool
test_e = absPath >=> \f ->
liftIO $ do
file <- doesFileExist f
if file then return True else doesDirectoryExist f
test_f :: FilePath -> Sh Bool
test_f = absPath >=> liftIO . doesFileExist
test_px :: FilePath -> Sh Bool
test_px exe = do
mFull <- which exe
case mFull of
Nothing -> return False
Just full -> liftIO $ isExecutable full
rm_rf :: FilePath -> Sh ()
rm_rf infp = do
f <- traceAbsPath ("rm -rf " <>) infp
isDir <- (test_d f)
if not isDir then whenM (test_f f) $ rm_f f
else
(liftIO_ $ removeDirectoryRecursive f) `catch_sh` (\(e :: IOError) ->
when (isPermissionError e) $ do
find f >>= mapM_ (\file -> liftIO_ $ fixPermissions file `catchany` \_ -> return ())
liftIO $ removeDirectoryRecursive f
)
where fixPermissions file =
do permissions <- liftIO $ getPermissions file
let deletable = permissions { readable = True, writable = True, executable = True }
liftIO $ setPermissions file deletable
rm_f :: FilePath -> Sh ()
rm_f = traceAbsPath ("rm -f " <>) >=> \f ->
whenM (test_e f) $ liftIO $ removeFile f
rm :: FilePath -> Sh ()
rm = traceAbsPath ("rm " <>) >=>
liftIO . removeFile
setenv :: Text -> Text -> Sh ()
setenv k v = if k == path_env then setPath v else setenvRaw k v
setenvRaw :: Text -> Text -> Sh ()
setenvRaw k v = modify $ \x -> x { sEnvironment = wibble $ sEnvironment x }
where
normK = normalizeEnvVarNameText k
(kStr, vStr) = (T.unpack normK, T.unpack v)
wibble environment = (kStr, vStr) : filter ((/=kStr) . fst) environment
setPath :: Text -> Sh ()
setPath newPath = do
modify $ \x -> x{ sPathExecutables = Nothing }
setenvRaw path_env newPath
path_env :: Text
path_env = normalizeEnvVarNameText "PATH"
appendToPath :: FilePath -> Sh ()
appendToPath = traceAbsPath ("appendToPath: " <>) >=> \filepath -> do
tp <- toTextWarn filepath
pe <- get_env_text path_env
setPath $ pe <> T.singleton searchPathSeparator <> tp
prependToPath :: FilePath -> Sh ()
prependToPath = traceAbsPath ("prependToPath: " <>) >=> \filepath -> do
tp <- toTextWarn filepath
pe <- get_env_text path_env
setPath $ tp <> T.singleton searchPathSeparator <> pe
get_environment :: Sh [(String, String)]
get_environment = gets sEnvironment
{-# DEPRECATED get_environment "use get_env_all" #-}
get_env_all :: Sh [(String, String)]
get_env_all = gets sEnvironment
#if defined(mingw32_HOST_OS)
normalizeEnvVarNameText :: Text -> Text
normalizeEnvVarNameText = T.toLower
normalizeEnvVarNameString :: String -> String
normalizeEnvVarNameString = fmap toLower
#else
normalizeEnvVarNameText :: Text -> Text
normalizeEnvVarNameText = id
normalizeEnvVarNameString :: String -> String
normalizeEnvVarNameString = id
#endif
get_env :: Text -> Sh (Maybe Text)
get_env k = do
mval <- return
. fmap T.pack
. lookup (T.unpack normK)
=<< gets sEnvironment
return $ case mval of
Nothing -> Nothing
Just val -> if (not $ T.null val) then Just val else Nothing
where
normK = normalizeEnvVarNameText k
getenv :: Text -> Sh Text
getenv k = get_env_def k ""
{-# DEPRECATED getenv "use get_env or get_env_text" #-}
get_env_text :: Text -> Sh Text
get_env_text = get_env_def ""
get_env_def :: Text -> Text -> Sh Text
get_env_def d = get_env >=> return . fromMaybe d
{-# DEPRECATED get_env_def "use fromMaybe DEFAULT get_env" #-}
initOutputHandles :: HandleInitializer -> StdInit
initOutputHandles f = StdInit (const $ return ()) f f
initAllHandles :: HandleInitializer -> StdInit
initAllHandles f = StdInit f f f
onCommandHandles :: StdInit -> Sh a -> Sh a
onCommandHandles initHandles a =
sub $ modify (\x -> x { sInitCommandHandles = initHandles }) >> a
silently :: Sh a -> Sh a
silently a = sub $ modify (\x -> x
{ sPrintStdout = False
, sPrintStderr = False
, sPrintCommands = False
}) >> a
verbosely :: Sh a -> Sh a
verbosely a = sub $ modify (\x -> x
{ sPrintStdout = True
, sPrintStderr = True
, sPrintCommands = True
}) >> a
log_stdout_with :: (Text -> IO ()) -> Sh a -> Sh a
log_stdout_with logger a = sub $ modify (\s -> s { sPutStdout = logger })
>> a
log_stderr_with :: (Text -> IO ()) -> Sh a -> Sh a
log_stderr_with logger a = sub $ modify (\s -> s { sPutStderr = logger })
>> a
print_stdout :: Bool -> Sh a -> Sh a
print_stdout shouldPrint a =
sub $ modify (\x -> x { sPrintStdout = shouldPrint }) >> a
print_stderr :: Bool -> Sh a -> Sh a
print_stderr shouldPrint a =
sub $ modify (\x -> x { sPrintStderr = shouldPrint }) >> a
print_commands :: Bool -> Sh a -> Sh a
print_commands shouldPrint a = sub $ modify (\st -> st { sPrintCommands = shouldPrint }) >> a
sub :: Sh a -> Sh a
sub a = do
oldState <- get
modify $ \st -> st { sTrace = T.empty }
a `finally_sh` restoreState oldState
where
restoreState oldState = do
newState <- get
put oldState {
sTrace = sTrace oldState <> sTrace newState
, sCode = sCode newState
, sStderr = sStderr newState
, sStdin = sStdin newState
}
tracing :: Bool -> Sh a -> Sh a
tracing shouldTrace action = sub $ do
modify $ \st -> st { sTracing = shouldTrace }
action
escaping :: Bool -> Sh a -> Sh a
escaping shouldEscape action = sub $ do
modify $ \st -> st { sCommandEscaping = shouldEscape }
action
errExit :: Bool -> Sh a -> Sh a
errExit shouldExit action = sub $ do
modify $ \st -> st { sErrExit = shouldExit }
action
followSymlink :: Bool -> Sh a -> Sh a
followSymlink enableFollowSymlink action = sub $ do
modify $ \st -> st { sFollowSymlink = enableFollowSymlink }
action
defReadOnlyState :: ReadOnlyState
defReadOnlyState = ReadOnlyState { rosFailToDir = False }
shellyNoDir :: MonadIO m => Sh a -> m a
shellyNoDir = shelly' ReadOnlyState { rosFailToDir = False }
{-# DEPRECATED shellyNoDir "Just use shelly. The default settings have changed" #-}
shellyFailDir :: MonadIO m => Sh a -> m a
shellyFailDir = shelly' ReadOnlyState { rosFailToDir = True }
getNormalizedEnvironment :: IO [(String, String)]
getNormalizedEnvironment =
#if defined(mingw32_HOST_OS)
fmap (\(a, b) -> (normalizeEnvVarNameString a, b)) <$> getEnvironment
#else
getEnvironment
#endif
shelly :: MonadIO m => Sh a -> m a
shelly = shelly' defReadOnlyState
shelly' :: MonadIO m => ReadOnlyState -> Sh a -> m a
shelly' ros action = do
environment <- liftIO getNormalizedEnvironment
dir <- liftIO getCurrentDirectory
let def = State { sCode = 0
, sStdin = Nothing
, sStderr = T.empty
, sPutStdout = TIO.hPutStrLn stdout
, sPutStderr = TIO.hPutStrLn stderr
, sPrintStdout = True
, sPrintStderr = True
, sPrintCommands = False
, sInitCommandHandles = initAllHandles (const $ return ())
, sCommandEscaping = True
, sEnvironment = environment
, sTracing = True
, sTrace = T.empty
, sDirectory = dir
, sPathExecutables = Nothing
, sErrExit = True
, sReadOnly = ros
, sFollowSymlink = False
}
stref <- liftIO $ newIORef def
let caught =
action `catches_sh` [
ShellyHandler (\ex ->
case ex of
ExitSuccess -> liftIO $ throwIO ex
ExitFailure _ -> throwExplainedException ex
)
, ShellyHandler (\ex -> case ex of
QuietExit n -> liftIO $ throwIO $ ExitFailure n)
, ShellyHandler (\(ex::SomeException) -> throwExplainedException ex)
]
liftIO $ runSh caught stref
where
throwExplainedException :: Exception exception => exception -> Sh a
throwExplainedException ex = get >>= errorMsg >>= liftIO . throwIO . ReThrownException ex
errorMsg st =
if not (rosFailToDir $ sReadOnly st) then ranCommands else do
d <- pwd
sf <- shellyFile
let logFile = d</>shelly_dir</>sf
(writefile logFile trc >> return ("log of commands saved to: " <> logFile))
`catchany_sh` (\_ -> ranCommands)
where
trc = sTrace st
ranCommands = return . mappend "Ran commands: \n" . T.unpack $ trc
shelly_dir = ".shelly"
shellyFile = chdir_p shelly_dir $ do
fs <- ls "."
return $ pack $ show (nextNum fs) <> ".txt"
nextNum :: [FilePath] -> Int
nextNum [] = 1
nextNum fs = (+ 1) . maximum . map (readDef 1 . filter isDigit . takeFileName) $ fs
readDef :: Read a => a -> String -> a
readDef def = fromMaybe def . readMay
where
readMay :: Read a => String -> Maybe a
readMay s = case [x | (x,t) <- reads s, ("","") <- lex t] of
[x] -> Just x
_ -> Nothing
data RunFailed = RunFailed FilePath [Text] Int Text deriving (Typeable)
instance Show RunFailed where
show (RunFailed exe args code errs) =
let codeMsg = case code of
127 -> ". exit code 127 usually means the command does not exist (in the PATH)"
_ -> ""
in "error running: " ++ T.unpack (show_command exe args) ++
"\nexit status: " ++ show code ++ codeMsg ++ "\nstderr: " ++ T.unpack errs
instance Exception RunFailed
show_command :: FilePath -> [Text] -> Text
show_command exe args =
T.intercalate " " $ map quote (toTextIgnore exe : args)
where
quote t | T.any (== '\'') t = t
quote t | T.any isSpace t = surround '\'' t
quote t | otherwise = t
quoteOne :: Text -> Text
quoteOne t =
surround '\'' $ T.replace "'" "'\\''" t
quoteCommand :: FilePath -> [Text] -> Text
quoteCommand exe args =
T.intercalate " " $ map quoteOne (toTextIgnore exe : args)
surround :: Char -> Text -> Text
surround c t = T.cons c $ T.snoc t c
data SshMode = ParSsh | SeqSsh
sshPairs_ :: Text -> [(FilePath, [Text])] -> Sh ()
sshPairs_ _ [] = return ()
sshPairs_ server cmds = sshPairs' run_ server cmds
sshPairsPar_ :: Text -> [(FilePath, [Text])] -> Sh ()
sshPairsPar_ _ [] = return ()
sshPairsPar_ server cmds = sshPairsPar' run_ server cmds
sshPairs :: Text -> [(FilePath, [Text])] -> Sh Text
sshPairs _ [] = return ""
sshPairs server cmds = sshPairsWithOptions' run server [] cmds SeqSsh
sshPairsPar :: Text -> [(FilePath, [Text])] -> Sh Text
sshPairsPar _ [] = return ""
sshPairsPar server cmds = sshPairsWithOptions' run server [] cmds ParSsh
sshPairsPar' :: (FilePath -> [Text] -> Sh a) -> Text -> [(FilePath, [Text])] -> Sh a
sshPairsPar' run' server actions = sshPairsWithOptions' run' server [] actions ParSsh
sshPairs' :: (FilePath -> [Text] -> Sh a) -> Text -> [(FilePath, [Text])] -> Sh a
sshPairs' run' server actions = sshPairsWithOptions' run' server [] actions SeqSsh
sshPairsWithOptions :: Text
-> [Text]
-> [(FilePath, [Text])]
-> Sh Text
sshPairsWithOptions _ _ [] = return ""
sshPairsWithOptions server sshargs cmds = sshPairsWithOptions' run server sshargs cmds SeqSsh
sshPairsWithOptions' :: (FilePath -> [Text] -> Sh a) -> Text -> [Text] -> [(FilePath, [Text])] -> SshMode -> Sh a
sshPairsWithOptions' run' server sshargs actions mode = escaping False $ do
run' "ssh" ([server] ++ sshargs ++ [sshCommandText actions mode])
sshCommandText :: [(FilePath, [Text])] -> SshMode -> Text
sshCommandText actions mode =
quoteOne (foldl1 joiner (map (uncurry quoteCommand) actions))
where
joiner memo next = case mode of
SeqSsh -> memo <> " && " <> next
ParSsh -> memo <> " & " <> next
data QuietExit = QuietExit Int deriving (Show, Typeable)
instance Exception QuietExit
data ReThrownException e = ReThrownException e String deriving (Typeable)
instance Exception e => Exception (ReThrownException e)
instance Exception e => Show (ReThrownException e) where
show (ReThrownException ex msg) = "\n" ++
msg ++ "\n" ++ "Exception: " ++ show ex
run :: FilePath -> [Text] -> Sh Text
run fp args = return . lineSeqToText =<< runFoldLines mempty (|>) fp args
bash :: FilePath -> [Text] -> Sh Text
bash fp args = escaping False $ run "bash" $ bashArgs fp args
bash_ :: FilePath -> [Text] -> Sh ()
bash_ fp args = escaping False $ run_ "bash" $ bashArgs fp args
bashArgs :: FilePath -> [Text] -> [Text]
bashArgs fp args = ["-c", "'" <> sanitise (toTextIgnore fp : args) <> "'"]
where
sanitise = T.replace "'" "\'" . T.intercalate " "
bashPipeFail :: (FilePath -> [Text] -> Sh a) -> FilePath -> [Text] -> Sh a
bashPipeFail runner fp args = runner "set -o pipefail;" (toTextIgnore fp : args)
command :: FilePath -> [Text] -> [Text] -> Sh Text
command com args more_args = run com (args ++ more_args)
command_ :: FilePath -> [Text] -> [Text] -> Sh ()
command_ com args more_args = run_ com (args ++ more_args)
command1 :: FilePath -> [Text] -> Text -> [Text] -> Sh Text
command1 com args one_arg more_args = run com (args ++ [one_arg] ++ more_args)
command1_ :: FilePath -> [Text] -> Text -> [Text] -> Sh ()
command1_ com args one_arg more_args = run_ com (args ++ [one_arg] ++ more_args)
run_ :: FilePath -> [Text] -> Sh ()
run_ exe args = do
state <- get
if sPrintStdout state
then runWithColor_
else runFoldLines () (\_ _ -> ()) exe args
where
runWithColor_ =
runHandles exe args [OutHandle Inherit] $ \inH _ errH -> do
state <- get
errs <- liftIO $ do
hClose inH
errVar <- (putHandleIntoMVar mempty (|>) errH (sPutStderr state) (sPrintStderr state))
lineSeqToText `fmap` wait errVar
modify $ \state' -> state' { sStderr = errs }
return ()
liftIO_ :: IO a -> Sh ()
liftIO_ = void . liftIO
runHandle :: FilePath
-> [Text]
-> (Handle -> Sh a)
-> Sh a
runHandle exe args withHandle = runHandles exe args [] $ \_ outH errH -> do
state <- get
errVar <- liftIO $
(putHandleIntoMVar mempty (|>) errH (sPutStderr state) (sPrintStderr state))
res <- withHandle outH
errs <- liftIO $ lineSeqToText `fmap` wait errVar
modify $ \state' -> state' { sStderr = errs }
return res
runHandles :: FilePath
-> [Text]
-> [StdHandle]
-> (Handle -> Handle -> Handle -> Sh a)
-> Sh a
runHandles exe args reusedHandles withHandles = do
origstate <- get
let mStdin = sStdin origstate
put $ origstate { sStdin = Nothing, sCode = 0, sStderr = T.empty }
state <- get
let cmdString = show_command exe args
when (sPrintCommands state) $ echo cmdString
trace cmdString
let doRun = if sCommandEscaping state then runCommand else runCommandNoEscape
bracket_sh
(doRun reusedHandles state exe args)
(\(_,_,_,procH) -> (liftIO $ terminateProcess procH))
(\(inH,outH,errH,procH) -> do
liftIO $ do
inInit (sInitCommandHandles state) inH
outInit (sInitCommandHandles state) outH
errInit (sInitCommandHandles state) errH
liftIO $ case mStdin of
Just input -> TIO.hPutStr inH input
Nothing -> return ()
result <- withHandles inH outH errH
(ex, code) <- liftIO $ do
ex' <- waitForProcess procH
hClose outH `catchany` (const $ return ())
hClose errH `catchany` (const $ return ())
hClose inH `catchany` (const $ return ())
return $ case ex' of
ExitSuccess -> (ex', 0)
ExitFailure n -> (ex', n)
modify $ \state' -> state' { sCode = code }
case (sErrExit state, ex) of
(True, ExitFailure n) -> do
newState <- get
liftIO $ throwIO $ RunFailed exe args n (sStderr newState)
_ -> return result
)
runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a
runFoldLines start cb exe args =
runHandles exe args [] $ \inH outH errH -> do
state <- get
(errVar, outVar) <- liftIO $ do
hClose inH
liftM2 (,)
(putHandleIntoMVar mempty (|>) errH (sPutStderr state) (sPrintStderr state))
(putHandleIntoMVar start cb outH (sPutStdout state) (sPrintStdout state))
errs <- liftIO $ lineSeqToText `fmap` wait errVar
modify $ \state' -> state' { sStderr = errs }
liftIO $ wait outVar
putHandleIntoMVar :: a -> FoldCallback a
-> Handle
-> (Text -> IO ())
-> Bool
-> IO (Async a)
putHandleIntoMVar start cb outH putWrite shouldPrint = liftIO $ async $ do
if shouldPrint
then transferFoldHandleLines start cb outH putWrite
else foldHandleLines start cb outH
lastStderr :: Sh Text
lastStderr = gets sStderr
lastExitCode :: Sh Int
lastExitCode = gets sCode
setStdin :: Text -> Sh ()
setStdin input = modify $ \st -> st { sStdin = Just input }
(-|-) :: Sh Text -> Sh b -> Sh b
one -|- two = do
res <- print_stdout False one
setStdin res
two
cp_r :: FilePath -> FilePath -> Sh ()
cp_r from' to' = do
from <- absPath from'
fromIsDir <- (test_d from)
if not fromIsDir then cp_should_follow_symlinks False from' to' else do
trace $ "cp_r " <> toTextIgnore from <> " " <> toTextIgnore to'
to <- absPath to'
toIsDir <- test_d to
when (from == to) $ liftIO $ throwIO $ userError $ show $ "cp_r: " <>
toTextIgnore from <> " and " <> toTextIgnore to <> " are identical"
finalTo <- if not toIsDir then do
mkdir to
return to
else do
let d = to </> (last . splitPath $ takeDirectory (addTrailingPathSeparator from))
mkdir_p d >> return d
ls from >>= mapM_ (\item -> do
cp_r (from FP.</> takeFileName item) (finalTo FP.</> takeFileName item))
cp :: FilePath -> FilePath -> Sh ()
cp = cp_should_follow_symlinks True
cp_should_follow_symlinks :: Bool -> FilePath -> FilePath -> Sh ()
cp_should_follow_symlinks shouldFollowSymlinks from' to' = do
from <- absPath from'
to <- absPath to'
trace $ "cp " <> toTextIgnore from <> " " <> toTextIgnore to
to_dir <- test_d to
let to_loc = if to_dir then to FP.</> takeFileName from else to
if shouldFollowSymlinks then copyNormal from to_loc else do
isSymlink <- liftIO $ pathIsSymbolicLink from
if not isSymlink then copyNormal from to_loc else do
target <- liftIO $ getSymbolicLinkTarget from
liftIO $ createFileLink target to_loc
where
extraMsg :: String -> String -> String
extraMsg t f = "during copy from: " ++ f ++ " to: " ++ t
copyNormal from to = liftIO $ copyFile from to `catchany` (\e -> throwIO $
ReThrownException e (extraMsg to from)
)
withTmpDir :: (FilePath -> Sh a) -> Sh a
withTmpDir act = do
trace "withTmpDir"
dir <- liftIO getTemporaryDirectory
tid <- liftIO myThreadId
(pS, fhandle) <- liftIO $ openTempFile dir ("tmp" ++ filter isAlphaNum (show tid))
let p = pack pS
liftIO $ hClose fhandle
rm_f p
mkdir p
act p `finally_sh` rm_rf p
writefile :: FilePath -> Text -> Sh ()
writefile f' bits = do
f <- traceAbsPath ("writefile " <>) f'
liftIO (TIO.writeFile f bits)
writeBinary :: FilePath -> ByteString -> Sh ()
writeBinary f' bytes = do
f <- traceAbsPath ("writeBinary " <>) f'
liftIO (BS.writeFile f bytes)
touchfile :: FilePath -> Sh ()
touchfile = traceAbsPath ("touch " <>) >=> flip appendfile ""
appendfile :: FilePath -> Text -> Sh ()
appendfile f' bits = do
f <- traceAbsPath ("appendfile " <>) f'
liftIO (TIO.appendFile f bits)
readfile :: FilePath -> Sh Text
readfile = traceAbsPath ("readfile " <>) >=> \fp ->
readBinary fp >>=
return . TE.decodeUtf8With TE.lenientDecode
readBinary :: FilePath -> Sh ByteString
readBinary = traceAbsPath ("readBinary " <>)
>=> liftIO . BS.readFile
hasExt :: Text -> FilePath -> Bool
hasExt ext fp = T.pack (FP.takeExtension fp) == ext
time :: Sh a -> Sh (Double, a)
time what = sub $ do
trace "time"
t <- liftIO getCurrentTime
res <- what
t' <- liftIO getCurrentTime
return (realToFrac $ diffUTCTime t' t, res)
sleep :: Int -> Sh ()
sleep = liftIO . threadDelay . (1000 * 1000 *)
asyncSh :: Sh a -> Sh (Async a)
asyncSh proc = do
state <- get
liftIO $ async $ shelly (put state >> proc)
tracePath :: (FilePath -> Sh FilePath)
-> (Text -> Text)
-> FilePath
-> Sh FilePath
tracePath convert tracer infp =
(convert infp >>= \fp -> traceIt fp >> return fp)
`catchany_sh` (\e -> traceIt infp >> liftIO (throwIO e))
where traceIt = trace . tracer . toTextIgnore
traceAbsPath :: (Text -> Text) -> FilePath -> Sh FilePath
traceAbsPath = tracePath absPath
traceCanonicPath :: (Text -> Text) -> FilePath -> Sh FilePath
traceCanonicPath = tracePath canonic