{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module System.Hapistrano.Commands.Internal where
import Control.Monad.IO.Class
import Data.Char (isSpace)
import Data.List (dropWhileEnd)
import Data.Maybe (catMaybes, fromJust, mapMaybe)
import Data.Proxy
import Numeric.Natural
import Path
import System.Hapistrano.Types (TargetSystem (..))
class Command a where
type Result a :: *
renderCommand :: a -> String
parseResult :: Proxy a -> String -> Result a
data Whoami =
Whoami
deriving (Int -> Whoami -> ShowS
[Whoami] -> ShowS
Whoami -> String
(Int -> Whoami -> ShowS)
-> (Whoami -> String) -> ([Whoami] -> ShowS) -> Show Whoami
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Whoami] -> ShowS
$cshowList :: [Whoami] -> ShowS
show :: Whoami -> String
$cshow :: Whoami -> String
showsPrec :: Int -> Whoami -> ShowS
$cshowsPrec :: Int -> Whoami -> ShowS
Show, Whoami -> Whoami -> Bool
(Whoami -> Whoami -> Bool)
-> (Whoami -> Whoami -> Bool) -> Eq Whoami
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Whoami -> Whoami -> Bool
$c/= :: Whoami -> Whoami -> Bool
== :: Whoami -> Whoami -> Bool
$c== :: Whoami -> Whoami -> Bool
Eq, Eq Whoami
Eq Whoami
-> (Whoami -> Whoami -> Ordering)
-> (Whoami -> Whoami -> Bool)
-> (Whoami -> Whoami -> Bool)
-> (Whoami -> Whoami -> Bool)
-> (Whoami -> Whoami -> Bool)
-> (Whoami -> Whoami -> Whoami)
-> (Whoami -> Whoami -> Whoami)
-> Ord Whoami
Whoami -> Whoami -> Bool
Whoami -> Whoami -> Ordering
Whoami -> Whoami -> Whoami
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Whoami -> Whoami -> Whoami
$cmin :: Whoami -> Whoami -> Whoami
max :: Whoami -> Whoami -> Whoami
$cmax :: Whoami -> Whoami -> Whoami
>= :: Whoami -> Whoami -> Bool
$c>= :: Whoami -> Whoami -> Bool
> :: Whoami -> Whoami -> Bool
$c> :: Whoami -> Whoami -> Bool
<= :: Whoami -> Whoami -> Bool
$c<= :: Whoami -> Whoami -> Bool
< :: Whoami -> Whoami -> Bool
$c< :: Whoami -> Whoami -> Bool
compare :: Whoami -> Whoami -> Ordering
$ccompare :: Whoami -> Whoami -> Ordering
$cp1Ord :: Eq Whoami
Ord)
instance Command Whoami where
type Result Whoami = String
renderCommand :: Whoami -> String
renderCommand Whoami
Whoami = String
"whoami"
parseResult :: Proxy Whoami -> String -> Result Whoami
parseResult Proxy Whoami
Proxy = ShowS
String -> Result Whoami
trim
data Cd cmd =
Cd (Path Abs Dir) cmd
instance Command cmd => Command (Cd cmd) where
type Result (Cd cmd) = Result cmd
renderCommand :: Cd cmd -> String
renderCommand (Cd Path Abs Dir
path cmd
cmd) =
String
"(cd " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
quoteCmd (Path Abs Dir -> String
fromAbsDir Path Abs Dir
path) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" && " String -> ShowS
forall a. [a] -> [a] -> [a]
++ cmd -> String
forall a. Command a => a -> String
renderCommand cmd
cmd String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
parseResult :: Proxy (Cd cmd) -> String -> Result (Cd cmd)
parseResult Proxy (Cd cmd)
Proxy = Proxy cmd -> String -> Result cmd
forall a. Command a => Proxy a -> String -> Result a
parseResult (Proxy cmd
forall k (t :: k). Proxy t
Proxy :: Proxy cmd)
data MkDir =
MkDir (Path Abs Dir)
instance Command MkDir where
type Result MkDir = ()
renderCommand :: MkDir -> String
renderCommand (MkDir Path Abs Dir
path) =
String -> [Maybe String] -> String
formatCmd String
"mkdir" [String -> Maybe String
forall a. a -> Maybe a
Just String
"-pv", String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
path)]
parseResult :: Proxy MkDir -> String -> Result MkDir
parseResult Proxy MkDir
Proxy String
_ = ()
data Rm where
Rm :: Path Abs t -> Rm
instance Command Rm where
type Result Rm = ()
renderCommand :: Rm -> String
renderCommand (Rm Path Abs t
path) = String -> [Maybe String] -> String
formatCmd String
"rm" [String -> Maybe String
forall a. a -> Maybe a
Just String
"-rf", String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs t -> String
forall b t. Path b t -> String
toFilePath Path Abs t
path)]
parseResult :: Proxy Rm -> String -> Result Rm
parseResult Proxy Rm
Proxy String
_ = ()
data Mv t =
Mv TargetSystem (Path Abs t) (Path Abs t)
instance Command (Mv File) where
type Result (Mv File) = ()
renderCommand :: Mv File -> String
renderCommand (Mv TargetSystem
ts Path Abs File
old Path Abs File
new) =
String -> [Maybe String] -> String
formatCmd String
"mv" [String -> Maybe String
forall a. a -> Maybe a
Just String
flags, String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
fromAbsFile Path Abs File
old), String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
fromAbsFile Path Abs File
new)]
where
flags :: String
flags =
if TargetSystem -> Bool
isLinux TargetSystem
ts
then String
"-fvT"
else String
"-fv"
parseResult :: Proxy (Mv File) -> String -> Result (Mv File)
parseResult Proxy (Mv File)
Proxy String
_ = ()
instance Command (Mv Dir) where
type Result (Mv Dir) = ()
renderCommand :: Mv Dir -> String
renderCommand (Mv TargetSystem
_ Path Abs Dir
old Path Abs Dir
new) =
String -> [Maybe String] -> String
formatCmd String
"mv" [String -> Maybe String
forall a. a -> Maybe a
Just String
"-fv", String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
old), String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
new)]
parseResult :: Proxy (Mv Dir) -> String -> Result (Mv Dir)
parseResult Proxy (Mv Dir)
Proxy String
_ = ()
data Ln where
Ln :: TargetSystem -> Path Abs t -> Path Abs File -> Ln
instance Command Ln where
type Result Ln = ()
renderCommand :: Ln -> String
renderCommand (Ln TargetSystem
ts Path Abs t
target Path Abs File
linkName) =
String -> [Maybe String] -> String
formatCmd
String
"ln"
[String -> Maybe String
forall a. a -> Maybe a
Just String
flags, String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs t -> String
forall b t. Path b t -> String
toFilePath Path Abs t
target), String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
fromAbsFile Path Abs File
linkName)]
where
flags :: String
flags =
if TargetSystem -> Bool
isLinux TargetSystem
ts
then String
"-svT"
else String
"-sv"
parseResult :: Proxy Ln -> String -> Result Ln
parseResult Proxy Ln
Proxy String
_ = ()
data Readlink t =
Readlink TargetSystem (Path Abs File)
instance Command (Readlink File) where
type Result (Readlink File) = Path Abs File
renderCommand :: Readlink File -> String
renderCommand (Readlink TargetSystem
ts Path Abs File
path) =
String -> [Maybe String] -> String
formatCmd String
"readlink" [Maybe String
flags, String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
forall b t. Path b t -> String
toFilePath Path Abs File
path)]
where
flags :: Maybe String
flags =
if TargetSystem -> Bool
isLinux TargetSystem
ts
then String -> Maybe String
forall a. a -> Maybe a
Just String
"-f"
else Maybe String
forall a. Maybe a
Nothing
parseResult :: Proxy (Readlink File) -> String -> Result (Readlink File)
parseResult Proxy (Readlink File)
Proxy = Maybe (Path Abs File) -> Path Abs File
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Path Abs File) -> Path Abs File)
-> (String -> Maybe (Path Abs File)) -> String -> Path Abs File
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe (Path Abs File)
forall (m :: * -> *). MonadThrow m => String -> m (Path Abs File)
parseAbsFile (String -> Maybe (Path Abs File))
-> ShowS -> String -> Maybe (Path Abs File)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
trim
instance Command (Readlink Dir) where
type Result (Readlink Dir) = Path Abs Dir
renderCommand :: Readlink Dir -> String
renderCommand (Readlink TargetSystem
ts Path Abs File
path) =
String -> [Maybe String] -> String
formatCmd String
"readlink" [Maybe String
flags, String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
forall b t. Path b t -> String
toFilePath Path Abs File
path)]
where
flags :: Maybe String
flags =
if TargetSystem -> Bool
isLinux TargetSystem
ts
then String -> Maybe String
forall a. a -> Maybe a
Just String
"-f"
else Maybe String
forall a. Maybe a
Nothing
parseResult :: Proxy (Readlink Dir) -> String -> Result (Readlink Dir)
parseResult Proxy (Readlink Dir)
Proxy = Maybe (Path Abs Dir) -> Path Abs Dir
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Path Abs Dir) -> Path Abs Dir)
-> (String -> Maybe (Path Abs Dir)) -> String -> Path Abs Dir
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe (Path Abs Dir)
forall (m :: * -> *). MonadThrow m => String -> m (Path Abs Dir)
parseAbsDir (String -> Maybe (Path Abs Dir))
-> ShowS -> String -> Maybe (Path Abs Dir)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
trim
data Ls =
Ls (Path Abs Dir)
instance Command Ls where
type Result Ls = ()
renderCommand :: Ls -> String
renderCommand (Ls Path Abs Dir
path) = String -> [Maybe String] -> String
formatCmd String
"ls" [String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
path)]
parseResult :: Proxy Ls -> String -> Result Ls
parseResult Proxy Ls
Proxy String
_ = ()
data Find t =
Find Natural (Path Abs Dir)
instance Command (Find Dir) where
type Result (Find Dir) = [Path Abs Dir]
renderCommand :: Find Dir -> String
renderCommand (Find Natural
maxDepth Path Abs Dir
dir) =
String -> [Maybe String] -> String
formatCmd
String
"find"
[ String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
dir)
, String -> Maybe String
forall a. a -> Maybe a
Just String
"-maxdepth"
, String -> Maybe String
forall a. a -> Maybe a
Just (Natural -> String
forall a. Show a => a -> String
show Natural
maxDepth)
, String -> Maybe String
forall a. a -> Maybe a
Just String
"-type"
, String -> Maybe String
forall a. a -> Maybe a
Just String
"d"
]
parseResult :: Proxy (Find Dir) -> String -> Result (Find Dir)
parseResult Proxy (Find Dir)
Proxy = (String -> Maybe (Path Abs Dir)) -> [String] -> [Path Abs Dir]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (String -> Maybe (Path Abs Dir)
forall (m :: * -> *). MonadThrow m => String -> m (Path Abs Dir)
parseAbsDir (String -> Maybe (Path Abs Dir))
-> ShowS -> String -> Maybe (Path Abs Dir)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
trim) ([String] -> [Path Abs Dir])
-> (String -> [String]) -> String -> [Path Abs Dir]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
instance Command (Find File) where
type Result (Find File) = [Path Abs File]
renderCommand :: Find File -> String
renderCommand (Find Natural
maxDepth Path Abs Dir
dir) =
String -> [Maybe String] -> String
formatCmd
String
"find"
[ String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
dir)
, String -> Maybe String
forall a. a -> Maybe a
Just String
"-maxdepth"
, String -> Maybe String
forall a. a -> Maybe a
Just (Natural -> String
forall a. Show a => a -> String
show Natural
maxDepth)
, String -> Maybe String
forall a. a -> Maybe a
Just String
"-type"
, String -> Maybe String
forall a. a -> Maybe a
Just String
"f"
]
parseResult :: Proxy (Find File) -> String -> Result (Find File)
parseResult Proxy (Find File)
Proxy = (String -> Maybe (Path Abs File)) -> [String] -> [Path Abs File]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (String -> Maybe (Path Abs File)
forall (m :: * -> *). MonadThrow m => String -> m (Path Abs File)
parseAbsFile (String -> Maybe (Path Abs File))
-> ShowS -> String -> Maybe (Path Abs File)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
trim) ([String] -> [Path Abs File])
-> (String -> [String]) -> String -> [Path Abs File]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
data Touch =
Touch (Path Abs File)
instance Command Touch where
type Result Touch = ()
renderCommand :: Touch -> String
renderCommand (Touch Path Abs File
path) = String -> [Maybe String] -> String
formatCmd String
"touch" [String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs File -> String
fromAbsFile Path Abs File
path)]
parseResult :: Proxy Touch -> String -> Result Touch
parseResult Proxy Touch
Proxy String
_ = ()
data GitCheckout =
GitCheckout String
instance Command GitCheckout where
type Result GitCheckout = ()
renderCommand :: GitCheckout -> String
renderCommand (GitCheckout String
revision) =
String -> [Maybe String] -> String
formatCmd String
"git" [String -> Maybe String
forall a. a -> Maybe a
Just String
"checkout", String -> Maybe String
forall a. a -> Maybe a
Just String
revision]
parseResult :: Proxy GitCheckout -> String -> Result GitCheckout
parseResult Proxy GitCheckout
Proxy String
_ = ()
data GitClone =
GitClone Bool (Either String (Path Abs Dir)) (Path Abs Dir)
instance Command GitClone where
type Result GitClone = ()
renderCommand :: GitClone -> String
renderCommand (GitClone Bool
bare Either String (Path Abs Dir)
src Path Abs Dir
dest) =
String -> [Maybe String] -> String
formatCmd
String
"git"
[ String -> Maybe String
forall a. a -> Maybe a
Just String
"clone"
, if Bool
bare
then String -> Maybe String
forall a. a -> Maybe a
Just String
"--bare"
else Maybe String
forall a. Maybe a
Nothing
, String -> Maybe String
forall a. a -> Maybe a
Just
(case Either String (Path Abs Dir)
src of
Left String
repoUrl -> String
repoUrl
Right Path Abs Dir
srcPath -> Path Abs Dir -> String
fromAbsDir Path Abs Dir
srcPath)
, String -> Maybe String
forall a. a -> Maybe a
Just (Path Abs Dir -> String
fromAbsDir Path Abs Dir
dest)
]
parseResult :: Proxy GitClone -> String -> Result GitClone
parseResult Proxy GitClone
Proxy String
_ = ()
data GitFetch =
GitFetch String
instance Command GitFetch where
type Result GitFetch = ()
renderCommand :: GitFetch -> String
renderCommand (GitFetch String
remote) =
String -> [Maybe String] -> String
formatCmd
String
"git"
[String -> Maybe String
forall a. a -> Maybe a
Just String
"fetch", String -> Maybe String
forall a. a -> Maybe a
Just String
remote, String -> Maybe String
forall a. a -> Maybe a
Just String
"+refs/heads/\\*:refs/heads/\\*"]
parseResult :: Proxy GitFetch -> String -> Result GitFetch
parseResult Proxy GitFetch
Proxy String
_ = ()
data GitReset =
GitReset String
instance Command GitReset where
type Result GitReset = ()
renderCommand :: GitReset -> String
renderCommand (GitReset String
revision) =
String -> [Maybe String] -> String
formatCmd String
"git" [String -> Maybe String
forall a. a -> Maybe a
Just String
"reset", String -> Maybe String
forall a. a -> Maybe a
Just String
revision]
parseResult :: Proxy GitReset -> String -> Result GitReset
parseResult Proxy GitReset
Proxy String
_ = ()
data GenericCommand =
GenericCommand String
deriving (Int -> GenericCommand -> ShowS
[GenericCommand] -> ShowS
GenericCommand -> String
(Int -> GenericCommand -> ShowS)
-> (GenericCommand -> String)
-> ([GenericCommand] -> ShowS)
-> Show GenericCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenericCommand] -> ShowS
$cshowList :: [GenericCommand] -> ShowS
show :: GenericCommand -> String
$cshow :: GenericCommand -> String
showsPrec :: Int -> GenericCommand -> ShowS
$cshowsPrec :: Int -> GenericCommand -> ShowS
Show, GenericCommand -> GenericCommand -> Bool
(GenericCommand -> GenericCommand -> Bool)
-> (GenericCommand -> GenericCommand -> Bool) -> Eq GenericCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenericCommand -> GenericCommand -> Bool
$c/= :: GenericCommand -> GenericCommand -> Bool
== :: GenericCommand -> GenericCommand -> Bool
$c== :: GenericCommand -> GenericCommand -> Bool
Eq, Eq GenericCommand
Eq GenericCommand
-> (GenericCommand -> GenericCommand -> Ordering)
-> (GenericCommand -> GenericCommand -> Bool)
-> (GenericCommand -> GenericCommand -> Bool)
-> (GenericCommand -> GenericCommand -> Bool)
-> (GenericCommand -> GenericCommand -> Bool)
-> (GenericCommand -> GenericCommand -> GenericCommand)
-> (GenericCommand -> GenericCommand -> GenericCommand)
-> Ord GenericCommand
GenericCommand -> GenericCommand -> Bool
GenericCommand -> GenericCommand -> Ordering
GenericCommand -> GenericCommand -> GenericCommand
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GenericCommand -> GenericCommand -> GenericCommand
$cmin :: GenericCommand -> GenericCommand -> GenericCommand
max :: GenericCommand -> GenericCommand -> GenericCommand
$cmax :: GenericCommand -> GenericCommand -> GenericCommand
>= :: GenericCommand -> GenericCommand -> Bool
$c>= :: GenericCommand -> GenericCommand -> Bool
> :: GenericCommand -> GenericCommand -> Bool
$c> :: GenericCommand -> GenericCommand -> Bool
<= :: GenericCommand -> GenericCommand -> Bool
$c<= :: GenericCommand -> GenericCommand -> Bool
< :: GenericCommand -> GenericCommand -> Bool
$c< :: GenericCommand -> GenericCommand -> Bool
compare :: GenericCommand -> GenericCommand -> Ordering
$ccompare :: GenericCommand -> GenericCommand -> Ordering
$cp1Ord :: Eq GenericCommand
Ord)
instance Command GenericCommand where
type Result GenericCommand = ()
renderCommand :: GenericCommand -> String
renderCommand (GenericCommand String
cmd) = String
cmd
parseResult :: Proxy GenericCommand -> String -> Result GenericCommand
parseResult Proxy GenericCommand
Proxy String
_ = ()
mkGenericCommand :: String -> Maybe GenericCommand
mkGenericCommand :: String -> Maybe GenericCommand
mkGenericCommand String
str =
if Char
'\n' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
str' Bool -> Bool -> Bool
|| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str'
then Maybe GenericCommand
forall a. Maybe a
Nothing
else GenericCommand -> Maybe GenericCommand
forall a. a -> Maybe a
Just (String -> GenericCommand
GenericCommand String
str')
where
str' :: String
str' = ShowS
trim ((Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'#') String
str)
unGenericCommand :: GenericCommand -> String
unGenericCommand :: GenericCommand -> String
unGenericCommand (GenericCommand String
x) = String
x
readScript :: MonadIO m => Path Abs File -> m [GenericCommand]
readScript :: Path Abs File -> m [GenericCommand]
readScript Path Abs File
path =
IO [GenericCommand] -> m [GenericCommand]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GenericCommand] -> m [GenericCommand])
-> IO [GenericCommand] -> m [GenericCommand]
forall a b. (a -> b) -> a -> b
$ (String -> Maybe GenericCommand) -> [String] -> [GenericCommand]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe String -> Maybe GenericCommand
mkGenericCommand ([String] -> [GenericCommand])
-> (String -> [String]) -> String -> [GenericCommand]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines (String -> [GenericCommand]) -> IO String -> IO [GenericCommand]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
readFile (Path Abs File -> String
fromAbsFile Path Abs File
path)
formatCmd :: String -> [Maybe String] -> String
formatCmd :: String -> [Maybe String] -> String
formatCmd String
cmd [Maybe String]
args = [String] -> String
unwords (ShowS
quoteCmd ShowS -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String
cmd String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [Maybe String] -> [String]
forall a. [Maybe a] -> [a]
catMaybes [Maybe String]
args))
quoteCmd :: String -> String
quoteCmd :: ShowS
quoteCmd String
str =
if (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isSpace String
str
then String
"\"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\""
else String
str
trim :: String -> String
trim :: ShowS
trim = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd Char -> Bool
isSpace ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace
isLinux :: TargetSystem -> Bool
isLinux :: TargetSystem -> Bool
isLinux = (TargetSystem -> TargetSystem -> Bool
forall a. Eq a => a -> a -> Bool
== TargetSystem
GNULinux)