diff --git a/examples/Pipe/Log.hs b/examples/Pipe/Log.hs index 64f64b8..78bff29 100644 --- a/examples/Pipe/Log.hs +++ b/examples/Pipe/Log.hs @@ -12,13 +12,11 @@ import Data.Text.Lazy as LT default (LT.Text) main = shs $ do - makeLog + makeLog appendfile logFile . cons '\n' =<< liftSh sort (lsT ".") logFile = "log" -makeLog = - unlessM (test_f logFile) +makeLog = + unlessM (test_f logFile) (touchfile logFile) - - diff --git a/examples/Pipe/Pictures.hs b/examples/Pipe/Pictures.hs index 781f66a..8372563 100644 --- a/examples/Pipe/Pictures.hs +++ b/examples/Pipe/Pictures.hs @@ -1,4 +1,4 @@ --- | Suppose we have a directory named "pictures". +-- | Suppose we have a directory named "pictures". -- We want to copy all files with specified extensions. -- So that jpgs go in one directory and pngs in the other. {-# LANGUAGE OverloadedStrings #-} @@ -23,11 +23,9 @@ pictures :: FilePath pictures = "pictures" proc :: Text -> Sh () -proc ext = do +proc ext = do mkdir_p ext' findExt ext pictures >>= flip cp ext' where ext' = fromText ext findExt a = findWhen (pure . hasExt a) - - diff --git a/shelly-extra/Shelly/Background.hs b/shelly-extra/Shelly/Background.hs index 16fb2a3..65aec58 100644 --- a/shelly-extra/Shelly/Background.hs +++ b/shelly-extra/Shelly/Background.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, ExistentialQuantification #-} -- | A futures implementation that integrates with shelly --- +-- -- > jobs 5 (\job -> background job (sleep 2) >> background job (sleep 1)) -- -- 'jobs' will wait for all concurrent jobs to finish. diff --git a/shelly-extra/test/main.hs b/shelly-extra/test/main.hs index 41f218d..995ff37 100644 --- a/shelly-extra/test/main.hs +++ b/shelly-extra/test/main.hs @@ -50,6 +50,6 @@ main = do echo "immediate2" _<- background job $ cmd "sleep" "2" echo "blocked by background " - + echo "blocked by jobs" diff --git a/src/Shelly.hs b/src/Shelly.hs index 38d9ab9..e2e1990 100644 --- a/src/Shelly.hs +++ b/src/Shelly.hs @@ -516,7 +516,7 @@ mv from' to' = do 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 + if not from_dir then liftIO $ renameFile from to_loc `catchany` (\e -> throwIO $ ReThrownException e (extraMsg to_loc from) @@ -1415,11 +1415,11 @@ cp_r from' to' = do 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 + finalTo <- if not toIsDir then do + mkdir to + return to else do - -- this takes the name of the from directory + -- this takes the name of the from directory -- because filepath has no builtin function like `dirname` let d = to (last . splitPath $ takeDirectory (addTrailingPathSeparator from)) mkdir_p d >> return d diff --git a/src/Shelly/Base.hs b/src/Shelly/Base.hs index c7c52ae..2e31759 100644 --- a/src/Shelly/Base.hs +++ b/src/Shelly/Base.hs @@ -177,8 +177,8 @@ eitherRelativeTo relativeFP fp = do -> Sh (Either FilePath FilePath) stripIt rel toStrip nada = let stripped = FP.makeRelative rel toStrip - in if stripped == toStrip - then nada + in if stripped == toStrip + then nada else return $ Right stripped -- | make the second path relative to the first @@ -231,7 +231,7 @@ instance Exception EmptyFilePathError -- To create a relative path, use 'relPath'. absPath :: FilePath -> Sh FilePath absPath p | null p = liftIO $ throwIO EmptyFilePathError - | isRelative p = do + | isRelative p = do cwd <- gets sDirectory return (cwd FP. p) | otherwise = return p @@ -321,4 +321,3 @@ traceEcho msg = trace ("echo " `mappend` "'" `mappend` msg `mappend` "'") -- @... `catch` \(e :: SomeException) -> ...@). catchany :: IO a -> (SomeException -> IO a) -> IO a catchany = catch - diff --git a/src/Shelly/Pipe.hs b/src/Shelly/Pipe.hs index ea9fe92..b60bad9 100644 --- a/src/Shelly/Pipe.hs +++ b/src/Shelly/Pipe.hs @@ -1,14 +1,14 @@ -{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, +{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, TypeFamilies, ExistentialQuantification #-} --- | This module is a wrapper for the module "Shelly". --- The only difference is a main type 'Sh'. In this module +-- | This module is a wrapper for the module "Shelly". +-- The only difference is a main type 'Sh'. In this module -- 'Sh' contains a list of results. Actual definition of the type 'Sh' is: -- -- > import qualified Shelly as S -- > -- > newtype Sh a = Sh { unSh :: S.Sh [a] } -- --- This definition can simplify some filesystem commands. +-- This definition can simplify some filesystem commands. -- A monad bind operator becomes a pipe operator and we can write -- -- > findExt ext = findWhen (pure . hasExt ext) @@ -17,12 +17,12 @@ -- > main = shs $ do -- > mkdir "new" -- > findExt "hs" "." >>= flip cp "new" --- > findExt "cpp" "." >>= rm_f +-- > findExt "cpp" "." >>= rm_f -- > liftIO $ putStrLn "done" -- -- Monad methods "return" and ">>=" behave like methods for --- @ListT Shelly.Sh@, but ">>" forgets the number of --- the empty effects. So the last line prints @\"done\"@ only once. +-- @ListT Shelly.Sh@, but ">>" forgets the number of +-- the empty effects. So the last line prints @\"done\"@ only once. -- -- Documentation in this module mostly just reference documentation from -- the main "Shelly" module. @@ -73,7 +73,7 @@ module Shelly.Pipe , exit, errorExit, quietExit, terror -- * Exceptions - , catchany, catch_sh, finally_sh + , catchany, catch_sh, finally_sh , ShellyHandler(..), catches_sh , catchany_sh @@ -89,7 +89,7 @@ module Shelly.Pipe -- * internal functions for writing extensions , get, put - -- * find functions + -- * find functions , find, findWhen, findFold , findDirFilter, findDirFilterWhen, findFoldDirFilter , followSymlink @@ -122,14 +122,14 @@ import Data.Text as T hiding (concat, all, find, cons) -- | This type is a simple wrapper for a type @Shelly.Sh@. --- 'Sh' contains a list of results. +-- 'Sh' contains a list of results. newtype Sh a = Sh { unSh :: S.Sh [a] } instance Functor Sh where - fmap f = Sh . fmap (fmap f) . unSh + fmap f = Sh . fmap (fmap f) . unSh instance Monad Sh where - return = Sh . return . return + return = Sh . return . return a >>= f = Sh $ fmap concat $ mapM (unSh . f) =<< unSh a a >> b = Sh $ unSh a >> unSh b @@ -154,29 +154,29 @@ instance MonadIO Sh where sh0 :: S.Sh a -> Sh a sh0 = Sh . fmap return -sh1 :: (a -> S.Sh b) -> (a -> Sh b) +sh1 :: (a -> S.Sh b) -> (a -> Sh b) sh1 f = \a -> sh0 (f a) -sh2 :: (a1 -> a2 -> S.Sh b) -> (a1 -> a2 -> Sh b) +sh2 :: (a1 -> a2 -> S.Sh b) -> (a1 -> a2 -> Sh b) sh2 f = \a b -> sh0 (f a b) -sh3 :: (a1 -> a2 -> a3 -> S.Sh b) -> (a1 -> a2 -> a3 -> Sh b) +sh3 :: (a1 -> a2 -> a3 -> S.Sh b) -> (a1 -> a2 -> a3 -> Sh b) sh3 f = \a b c -> sh0 (f a b c) -sh4 :: (a1 -> a2 -> a3 -> a4 -> S.Sh b) -> (a1 -> a2 -> a3 -> a4 -> Sh b) +sh4 :: (a1 -> a2 -> a3 -> a4 -> S.Sh b) -> (a1 -> a2 -> a3 -> a4 -> Sh b) sh4 f = \a b c d -> sh0 (f a b c d) sh0s :: S.Sh [a] -> Sh a sh0s = Sh -sh1s :: (a -> S.Sh [b]) -> (a -> Sh b) +sh1s :: (a -> S.Sh [b]) -> (a -> Sh b) sh1s f = \a -> sh0s (f a) {- Just in case ... -sh2s :: (a1 -> a2 -> S.Sh [b]) -> (a1 -> a2 -> Sh b) +sh2s :: (a1 -> a2 -> S.Sh [b]) -> (a1 -> a2 -> Sh b) sh2s f = \a b -> sh0s (f a b) -sh3s :: (a1 -> a2 -> a3 -> S.Sh [b]) -> (a1 -> a2 -> a3 -> Sh b) +sh3s :: (a1 -> a2 -> a3 -> S.Sh [b]) -> (a1 -> a2 -> a3 -> Sh b) sh3s f = \a b c -> sh0s (f a b c) -} @@ -188,19 +188,19 @@ lift2 f a b = Sh $ join $ liftA2 (mapM2 f') (unSh a) (unSh b) where f' = \x y -> f (return x) (return y) mapM2 :: Monad m => (a -> b -> m c)-> [a] -> [b] -> m [c] -mapM2 f as bs = sequence $ liftA2 f as bs +mapM2 f as bs = sequence $ liftA2 f as bs ----------------------------------------------------------- -- | Unpack list of results. unroll :: Sh a -> Sh [a] -unroll = Sh . fmap return . unSh +unroll = Sh . fmap return . unSh -- | Pack list of results. It performs @concat@ inside 'Sh'. roll :: Sh [a] -> Sh a roll = Sh . fmap concat . unSh --- | Transform result as list. It can be useful for filtering. +-- | Transform result as list. It can be useful for filtering. liftSh :: ([a] -> [b]) -> Sh a -> Sh b liftSh f = Sh . fmap f . unSh @@ -211,7 +211,7 @@ liftSh f = Sh . fmap f . unSh shelly :: MonadIO m => Sh a -> m [a] shelly = S.shelly . unSh --- | Performs 'shelly' and then an empty action @return ()@. +-- | Performs 'shelly' and then an empty action @return ()@. shs :: MonadIO m => Sh () -> m () shs x = shelly x >> return () @@ -289,7 +289,7 @@ lastStderr = sh0 S.lastStderr -- | see 'S.setStdin' setStdin :: Text -> Sh () -setStdin = sh1 S.setStdin +setStdin = sh1 S.setStdin -- | see 'S.lastExitCode' lastExitCode :: Sh Int @@ -358,7 +358,7 @@ pwd :: Sh FilePath pwd = sh0 S.pwd ----------------------------------------------------------------- --- Printing +-- Printing -- | Echo text to standard (error, when using _err variants) output. The _n -- variants do not print a final newline. @@ -528,15 +528,15 @@ findFold cons nil a = Sh $ S.findFold cons' nil' a -- | see 'S.findDirFilter' findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh FilePath findDirFilter p a = Sh $ S.findDirFilter (fmap and . unSh . p) a - + -- | see 'S.findDirFilterWhen' findDirFilterWhen :: (FilePath -> Sh Bool) -- ^ directory filter -> (FilePath -> Sh Bool) -- ^ file filter -> FilePath -- ^ directory -> Sh FilePath -findDirFilterWhen dirPred filePred a = - Sh $ S.findDirFilterWhen - (fmap and . unSh . dirPred) +findDirFilterWhen dirPred filePred a = + Sh $ S.findDirFilterWhen + (fmap and . unSh . dirPred) (fmap and . unSh . filePred) a @@ -547,9 +547,9 @@ findFoldDirFilter cons nil p a = Sh $ S.findFoldDirFilter cons' nil' p' a where p' = fmap and . unSh . p nil' = return nil cons' as dir = unSh $ roll $ mapM (flip cons dir) as - + ----------------------------------------------------------- --- exiting the program +-- exiting the program -- | see 'S.exit' exit :: Int -> Sh () @@ -597,14 +597,14 @@ catches_sh a hs = Sh $ S.catches_sh (unSh a) (fmap convert hs) convert (ShellyHandler f) = S.ShellyHandler (unSh . f) ------------------------------------------------------------ --- convert between Text and FilePath +-- convert between Text and FilePath -- | see 'S.toTextWarn' toTextWarn :: FilePath -> Sh Text toTextWarn = sh1 S.toTextWarn ------------------------------------------------------------- --- internal functions for writing extension +-- internal functions for writing extension get :: Sh State get = sh0 S.get diff --git a/test/src/CopySpec.hs b/test/src/CopySpec.hs index c601c22..7fd476b 100644 --- a/test/src/CopySpec.hs +++ b/test/src/CopySpec.hs @@ -14,7 +14,7 @@ import Help copySpec :: Spec copySpec = do - let b = "b" + let b = "b" let c = "c" describe "cp file" $ do it "cp to same dir" $ diff --git a/test/src/EnvSpec.hs b/test/src/EnvSpec.hs index a7c7c42..c342f69 100644 --- a/test/src/EnvSpec.hs +++ b/test/src/EnvSpec.hs @@ -32,7 +32,7 @@ envSpec = do setenv "SHELLY" "test" get_env_text "SHELLY" assert $ res == "test" - + describe "get_env \"PATH\" (OS compatibility test)" $ do it "get_env" $ do res <- shelly $ get_env "PATH" diff --git a/test/src/MoveSpec.hs b/test/src/MoveSpec.hs index 606006c..a975a7c 100644 --- a/test/src/MoveSpec.hs +++ b/test/src/MoveSpec.hs @@ -5,7 +5,7 @@ import Help moveSpec :: Spec moveSpec = do - let b = "b" + let b = "b" let c = "c" describe "mv file" $ do it "to same dir" $ do @@ -15,7 +15,7 @@ moveSpec = do mv b c readfile c res @?= "testing" - + it "to other dir" $ do res <- shelly $ within_dir "test/a" $ do @@ -24,7 +24,7 @@ moveSpec = do mv b c readfile "c/b" res @?= "testing" - + describe "mv dir" $ do it "to dir does not exist: create the to dir" $ do res <- shelly $ @@ -36,7 +36,7 @@ moveSpec = do liftIO $ assert cIsDir test_f "c/d" assert res - + it "to dir exists: creates a nested directory, full to path given" $ do res <- shelly $ within_dir "test/a" $ do @@ -50,7 +50,7 @@ moveSpec = do liftIO $ assert bIsDir test_f "c/b/d" assert res - + it "to dir exists: creates a nested directory, partial to path given" $ do res <- shelly $ within_dir "test/a" $ do @@ -64,7 +64,7 @@ moveSpec = do liftIO $ assert bIsDir test_f "c/b/d" assert res - + {- it "mv the same dir" $ do shelly $ do diff --git a/test/src/ReadFileSpec.hs b/test/src/ReadFileSpec.hs index 0a7b4bb..0624a46 100644 --- a/test/src/ReadFileSpec.hs +++ b/test/src/ReadFileSpec.hs @@ -16,8 +16,8 @@ readFileSpec = describe "file with invalid encoding" $ do it "readBinary" $ do res <- shelly $ readBinary "test/data/zshrc" assert (BS.length res > 0) - + it "readfile" $ do res <- shelly $ readfile "test/data/zshrc" assert (T.length res > 0) - + diff --git a/test/src/WhichSpec.hs b/test/src/WhichSpec.hs index f1ea279..cd4aee8 100644 --- a/test/src/WhichSpec.hs +++ b/test/src/WhichSpec.hs @@ -11,7 +11,7 @@ whichSpec = describe "which" $ do it "recognizes cabal as a path executable" $ do res <- shelly $ test_px "find" True @?= res - + it "cannot find missing exe" $ do Nothing <- shelly $ which "alskjdf;ashlva;ousnva;nj" assert True