{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {- | Copyright: (c) 2019-2020 Kowainik SPDX-License-Identifier: MPL-2.0 Maintainer: Kowainik This module contains neat utilities to be able to work with shell commands in generic and simple way using just string literals. >>> "echo" ["Hello", "World!"] ⚙ echo Hello 'World!' Hello World! -} module Shellmet ( ($|) , ($^) , ($?) ) where import Control.Exception (catch) import Data.String (IsString (..)) import Data.Text (Text) import System.Process (callCommand, readProcess, showCommandForUser) import qualified Data.Text as T {- | This instance is needed to provide functionality to call commands by using simple string literals in 'IO' monad. >>> "ls" ["-1", "test"] ⚙ ls -1 test Doctest.hs -} instance (a ~ [Text], b ~ IO ()) => IsString (a -> b) where fromString :: String -> [Text] -> IO () fromString cmd args = do let cmdStr = showCommandForUser cmd (map T.unpack args) putStrLn $ "⚙ " ++ cmdStr callCommand cmdStr {-# INLINE fromString #-} {- | Run shell command with given options and return stripped stdout of the executed command. >>> "echo" $| ["Foo", "Bar"] "Foo Bar" -} infix 5 $| ($|) :: FilePath -> [Text] -> IO Text cmd $| args = T.strip . T.pack <$> readProcess cmd (map T.unpack args) "" {-# INLINE ($|) #-} {- | This operator runs shell command with given options but doesn't print the command itself. >>> "echo" $^ ["Foo", "Bar"] Foo Bar -} infix 5 $^ ($^) :: FilePath -> [Text] -> IO () cmd $^ args = callCommand $ showCommandForUser cmd (map T.unpack args) {-# INLINE ($^) #-} {- | Do some IO actions when process failed with 'IOError'. >>> "exit" ["0"] $? putStrLn "Command failed" ⚙ exit 0 >>> "exit" ["1"] $? putStrLn "Command failed" ⚙ exit 1 Command failed -} infixl 4 $? ($?) :: IO a -> IO a -> IO a action $? handler = action `catch` \(_ :: IOError) -> handler {-# INLINE ($?) #-}