{-# LANGUAGE TypeFamilies #-}
module System.Process.Lens.CommandSpec
(
arguments
, _ShellCommand
, _RawCommand
, IsShell(..)
, IsRaw(..)
, arguing
, shellOf
, rawOf
) where
import Control.Lens
import System.Process
_ShellCommand :: Prism' CmdSpec String
_ShellCommand = prism' ShellCommand $ \c -> case c of
ShellCommand s -> Just s
_ -> Nothing
_RawCommand :: Prism' CmdSpec (FilePath, [String])
_RawCommand = prism' (uncurry RawCommand) $ \c -> case c of
RawCommand fp s -> Just (fp, s)
_ -> Nothing
arguments :: Traversal' CmdSpec [String]
arguments = _RawCommand . traverse
class IsShell a where
_Shell :: Prism' a String
{-# MINIMAL _Shell #-}
instance IsShell CmdSpec where
_Shell = _ShellCommand
class IsRaw a where
_Raw :: Prism' a (FilePath, [String])
{-# MINIMAL _Raw #-}
instance IsRaw CmdSpec where
_Raw = _RawCommand
arguing :: String -> CmdSpec -> CmdSpec
arguing s = arguments <>~ [s]
shellOf :: IsShell a => String -> a
shellOf s = _Shell # s
rawOf :: IsRaw a => FilePath -> [String] -> a
rawOf fp ss = _Raw # (fp,ss)