{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Setup.Copy
( CopyFlags (..)
, emptyCopyFlags
, defaultCopyFlags
, copyCommand
) where
import Distribution.Compat.Prelude hiding (get)
import Prelude ()
import Distribution.ReadE
import Distribution.Simple.Command hiding (boolOpt, boolOpt')
import Distribution.Simple.Flag
import Distribution.Simple.InstallDirs
import Distribution.Simple.Utils
import Distribution.Verbosity
import Distribution.Simple.Setup.Common
data CopyFlags = CopyFlags
{ CopyFlags -> Flag CopyDest
copyDest :: Flag CopyDest
, CopyFlags -> Flag FilePath
copyDistPref :: Flag FilePath
, CopyFlags -> Flag Verbosity
copyVerbosity :: Flag Verbosity
,
CopyFlags -> [FilePath]
copyArgs :: [String]
, CopyFlags -> Flag FilePath
copyCabalFilePath :: Flag FilePath
}
deriving (Int -> CopyFlags -> ShowS
[CopyFlags] -> ShowS
CopyFlags -> FilePath
(Int -> CopyFlags -> ShowS)
-> (CopyFlags -> FilePath)
-> ([CopyFlags] -> ShowS)
-> Show CopyFlags
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CopyFlags -> ShowS
showsPrec :: Int -> CopyFlags -> ShowS
$cshow :: CopyFlags -> FilePath
show :: CopyFlags -> FilePath
$cshowList :: [CopyFlags] -> ShowS
showList :: [CopyFlags] -> ShowS
Show, (forall x. CopyFlags -> Rep CopyFlags x)
-> (forall x. Rep CopyFlags x -> CopyFlags) -> Generic CopyFlags
forall x. Rep CopyFlags x -> CopyFlags
forall x. CopyFlags -> Rep CopyFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CopyFlags -> Rep CopyFlags x
from :: forall x. CopyFlags -> Rep CopyFlags x
$cto :: forall x. Rep CopyFlags x -> CopyFlags
to :: forall x. Rep CopyFlags x -> CopyFlags
Generic)
instance Binary CopyFlags
instance Structured CopyFlags
defaultCopyFlags :: CopyFlags
defaultCopyFlags :: CopyFlags
defaultCopyFlags =
CopyFlags
{ copyDest :: Flag CopyDest
copyDest = CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag CopyDest
NoCopyDest
, copyDistPref :: Flag FilePath
copyDistPref = Flag FilePath
forall a. Flag a
NoFlag
, copyVerbosity :: Flag Verbosity
copyVerbosity = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal
, copyArgs :: [FilePath]
copyArgs = []
, copyCabalFilePath :: Flag FilePath
copyCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
}
copyCommand :: CommandUI CopyFlags
copyCommand :: CommandUI CopyFlags
copyCommand =
CommandUI
{ commandName :: FilePath
commandName = FilePath
"copy"
, commandSynopsis :: FilePath
commandSynopsis = FilePath
"Copy the files of all/specific components to install locations."
, commandDescription :: Maybe ShowS
commandDescription = ShowS -> Maybe ShowS
forall a. a -> Maybe a
Just (ShowS -> Maybe ShowS) -> ShowS -> Maybe ShowS
forall a b. (a -> b) -> a -> b
$ \FilePath
_ ->
ShowS
wrapText ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
FilePath
"Components encompass executables and libraries. "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"Does not call register, and allows a prefix at install time. "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"Without the --destdir flag, configure determines location.\n"
, commandNotes :: Maybe ShowS
commandNotes = ShowS -> Maybe ShowS
forall a. a -> Maybe a
Just (ShowS -> Maybe ShowS) -> ShowS -> Maybe ShowS
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
FilePath
"Examples:\n"
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
pname
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" copy "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" All the components in the package\n"
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
pname
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" copy foo "
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" A component (i.e. lib, exe, test suite)"
, commandUsage :: ShowS
commandUsage =
FilePath -> [FilePath] -> ShowS
usageAlternatives FilePath
"copy" ([FilePath] -> ShowS) -> [FilePath] -> ShowS
forall a b. (a -> b) -> a -> b
$
[ FilePath
"[FLAGS]"
, FilePath
"COMPONENTS [FLAGS]"
]
, commandDefaultFlags :: CopyFlags
commandDefaultFlags = CopyFlags
defaultCopyFlags
, commandOptions :: ShowOrParseArgs -> [OptionField CopyFlags]
commandOptions = \ShowOrParseArgs
showOrParseArgs -> case ShowOrParseArgs
showOrParseArgs of
ShowOrParseArgs
ShowArgs ->
(OptionField CopyFlags -> Bool)
-> [OptionField CopyFlags] -> [OptionField CopyFlags]
forall a. (a -> Bool) -> [a] -> [a]
filter
( (FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
"target-package-db"])
(FilePath -> Bool)
-> (OptionField CopyFlags -> FilePath)
-> OptionField CopyFlags
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionField CopyFlags -> FilePath
forall a. OptionField a -> FilePath
optionName
)
([OptionField CopyFlags] -> [OptionField CopyFlags])
-> [OptionField CopyFlags] -> [OptionField CopyFlags]
forall a b. (a -> b) -> a -> b
$ ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
ShowArgs
ShowOrParseArgs
ParseArgs -> ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
ParseArgs
}
copyOptions :: ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions :: ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
showOrParseArgs =
[ (CopyFlags -> Flag Verbosity)
-> (Flag Verbosity -> CopyFlags -> CopyFlags)
-> OptionField CopyFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity CopyFlags -> Flag Verbosity
copyVerbosity (\Flag Verbosity
v CopyFlags
flags -> CopyFlags
flags{copyVerbosity = v})
, (CopyFlags -> Flag FilePath)
-> (Flag FilePath -> CopyFlags -> CopyFlags)
-> ShowOrParseArgs
-> OptionField CopyFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
CopyFlags -> Flag FilePath
copyDistPref
(\Flag FilePath
d CopyFlags
flags -> CopyFlags
flags{copyDistPref = d})
ShowOrParseArgs
showOrParseArgs
, FilePath
-> [FilePath]
-> FilePath
-> (CopyFlags -> Flag CopyDest)
-> (Flag CopyDest -> CopyFlags -> CopyFlags)
-> MkOptDescr
(CopyFlags -> Flag CopyDest)
(Flag CopyDest -> CopyFlags -> CopyFlags)
CopyFlags
-> OptionField CopyFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
FilePath
""
[FilePath
"destdir"]
FilePath
"directory to copy files to, prepended to installation directories"
CopyFlags -> Flag CopyDest
copyDest
( \Flag CopyDest
v CopyFlags
flags -> case CopyFlags -> Flag CopyDest
copyDest CopyFlags
flags of
Flag (CopyToDb FilePath
_) -> FilePath -> CopyFlags
forall a. HasCallStack => FilePath -> a
error FilePath
"Use either 'destdir' or 'target-package-db'."
Flag CopyDest
_ -> CopyFlags
flags{copyDest = v}
)
( FilePath
-> ReadE (Flag CopyDest)
-> (Flag CopyDest -> [FilePath])
-> MkOptDescr
(CopyFlags -> Flag CopyDest)
(Flag CopyDest -> CopyFlags -> CopyFlags)
CopyFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
FilePath
"DIR"
((FilePath -> Flag CopyDest) -> ReadE (Flag CopyDest)
forall a. (FilePath -> a) -> ReadE a
succeedReadE (CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag (CopyDest -> Flag CopyDest)
-> (FilePath -> CopyDest) -> FilePath -> Flag CopyDest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> CopyDest
CopyTo))
(\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyTo FilePath
p) -> [FilePath
p]; Flag CopyDest
_ -> [])
)
, FilePath
-> [FilePath]
-> FilePath
-> (CopyFlags -> Flag CopyDest)
-> (Flag CopyDest -> CopyFlags -> CopyFlags)
-> MkOptDescr
(CopyFlags -> Flag CopyDest)
(Flag CopyDest -> CopyFlags -> CopyFlags)
CopyFlags
-> OptionField CopyFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
FilePath
""
[FilePath
"target-package-db"]
FilePath
"package database to copy files into. Required when using ${pkgroot} prefix."
CopyFlags -> Flag CopyDest
copyDest
( \Flag CopyDest
v CopyFlags
flags -> case CopyFlags -> Flag CopyDest
copyDest CopyFlags
flags of
Flag CopyDest
NoFlag -> CopyFlags
flags{copyDest = v}
Flag CopyDest
NoCopyDest -> CopyFlags
flags{copyDest = v}
Flag CopyDest
_ -> FilePath -> CopyFlags
forall a. HasCallStack => FilePath -> a
error FilePath
"Use either 'destdir' or 'target-package-db'."
)
( FilePath
-> ReadE (Flag CopyDest)
-> (Flag CopyDest -> [FilePath])
-> MkOptDescr
(CopyFlags -> Flag CopyDest)
(Flag CopyDest -> CopyFlags -> CopyFlags)
CopyFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
FilePath
"DATABASE"
((FilePath -> Flag CopyDest) -> ReadE (Flag CopyDest)
forall a. (FilePath -> a) -> ReadE a
succeedReadE (CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag (CopyDest -> Flag CopyDest)
-> (FilePath -> CopyDest) -> FilePath -> Flag CopyDest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> CopyDest
CopyToDb))
(\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyToDb FilePath
p) -> [FilePath
p]; Flag CopyDest
_ -> [])
)
]
emptyCopyFlags :: CopyFlags
emptyCopyFlags :: CopyFlags
emptyCopyFlags = CopyFlags
forall a. Monoid a => a
mempty
instance Monoid CopyFlags where
mempty :: CopyFlags
mempty = CopyFlags
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
mappend :: CopyFlags -> CopyFlags -> CopyFlags
mappend = CopyFlags -> CopyFlags -> CopyFlags
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup CopyFlags where
<> :: CopyFlags -> CopyFlags -> CopyFlags
(<>) = CopyFlags -> CopyFlags -> CopyFlags
forall a. (Generic a, GSemigroup (Rep a)) => a -> a -> a
gmappend