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