module Sys.CmdSpec(
CmdSpec(..)
, AsCmdSpec(..)
, AsExecutableName(..)
, AsExecutableArguments(..)
, AsShellCommand(..)
, AsRawCommand(..)
) where
import Control.Applicative(Applicative)
import Control.Category(Category(id, (.)))
import Control.Lens(Optic', Choice, Profunctor, prism', iso, _1, _2)
import Data.Eq(Eq)
import Data.Functor(Functor)
import Data.Maybe(Maybe(Just, Nothing))
import Data.Ord(Ord)
import Data.String(IsString(fromString), String)
import Data.Tuple(uncurry)
import Prelude(Show)
import System.FilePath(FilePath)
import qualified System.Process as Process
data CmdSpec =
ShellCommand String
| RawCommand FilePath [String]
deriving (Eq, Ord, Show)
instance IsString CmdSpec where
fromString =
ShellCommand
class AsCmdSpec p f s where
_CmdSpec ::
Optic' p f s CmdSpec
instance AsCmdSpec p f CmdSpec where
_CmdSpec =
id
instance (Profunctor p, Functor f) => AsCmdSpec p f Process.CmdSpec where
_CmdSpec =
iso
(\c -> case c of
Process.ShellCommand s ->
ShellCommand s
Process.RawCommand p s ->
RawCommand p s)
(\c -> case c of
ShellCommand s ->
Process.ShellCommand s
RawCommand p s ->
Process.RawCommand p s)
class AsExecutableName p f s where
_ExecutableName ::
Optic' p f s FilePath
instance AsExecutableName p f FilePath where
_ExecutableName =
id
instance Applicative f => AsExecutableName (->) f CmdSpec where
_ExecutableName =
_RawCommand . _1
class AsExecutableArguments p f s where
_ExecutableArguments ::
Optic' p f s [String]
instance AsExecutableArguments p f [String] where
_ExecutableArguments =
id
instance Applicative f => AsExecutableArguments (->) f CmdSpec where
_ExecutableArguments =
_RawCommand . _2
class AsShellCommand p f s where
_ShellCommand ::
Optic' p f s String
instance AsShellCommand p f String where
_ShellCommand =
id
instance (Choice p, Applicative f) => AsShellCommand p f CmdSpec where
_ShellCommand =
prism'
ShellCommand
(\c -> case c of
ShellCommand s ->
Just s
RawCommand _ _ ->
Nothing)
class AsRawCommand p f s where
_RawCommand ::
Optic' p f s (FilePath, [String])
instance AsRawCommand p f (FilePath, [String]) where
_RawCommand =
id
instance (Choice p, Applicative f) => AsRawCommand p f CmdSpec where
_RawCommand =
prism'
(uncurry RawCommand)
(\c -> case c of
ShellCommand _ ->
Nothing
RawCommand p s ->
Just (p, s))