{-# LANGUAGE OverloadedRecordDot #-}
module Cloudy.Cli
( parseCliOpts
, CliCmd(..)
, ScalewayCliOpts(..)
, AwsCliOpts(..)
, ListCliOpts(..)
, SshCliOpts(..)
, CopyFileCliOpts(..)
, DestroyCliOpts(..)
, CopyFileDirection(..)
, Recursive(..)
)
where
import Cloudy.Cli.Aws (AwsCliOpts(..), awsCliOptsParser)
import Cloudy.Cli.Scaleway (ScalewayCliOpts(..), scalewayCliOptsParser)
import Cloudy.Db (CloudyInstanceId (..), CloudyInstance (..), withCloudyDb, findAllCloudyInstances)
import Cloudy.InstanceSetup (getUserInstanceSetups)
import Cloudy.InstanceSetup.Types (InstanceSetup)
import Control.Applicative (Alternative(many), optional)
import Data.Int (Int64)
import Data.Text (Text, unpack)
import Data.Version (showVersion)
import Options.Applicative
( Alternative((<|>)), Parser, (<**>), command, fullDesc, header, info
, progDesc, execParser, helper, footer, hsubparser, ParserInfo, strOption, long, short, metavar, help, option, auto, noIntersperse, forwardOptions, strArgument, footerDoc, flag', flag, completeWith, simpleVersioner )
import Options.Applicative.Help (vsep)
import Paths_cloudy (version)
data CliCmd
= Aws AwsCliOpts
| List ListCliOpts
| Scaleway ScalewayCliOpts
| Ssh SshCliOpts
| CopyFile CopyFileCliOpts
| Destroy DestroyCliOpts
deriving stock Int -> CliCmd -> ShowS
[CliCmd] -> ShowS
CliCmd -> String
(Int -> CliCmd -> ShowS)
-> (CliCmd -> String) -> ([CliCmd] -> ShowS) -> Show CliCmd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CliCmd -> ShowS
showsPrec :: Int -> CliCmd -> ShowS
$cshow :: CliCmd -> String
show :: CliCmd -> String
$cshowList :: [CliCmd] -> ShowS
showList :: [CliCmd] -> ShowS
Show
data ListCliOpts = ListCliOpts
deriving stock Int -> ListCliOpts -> ShowS
[ListCliOpts] -> ShowS
ListCliOpts -> String
(Int -> ListCliOpts -> ShowS)
-> (ListCliOpts -> String)
-> ([ListCliOpts] -> ShowS)
-> Show ListCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListCliOpts -> ShowS
showsPrec :: Int -> ListCliOpts -> ShowS
$cshow :: ListCliOpts -> String
show :: ListCliOpts -> String
$cshowList :: [ListCliOpts] -> ShowS
showList :: [ListCliOpts] -> ShowS
Show
data SshCliOpts = SshCliOpts
{ SshCliOpts -> Maybe CloudyInstanceId
id :: Maybe CloudyInstanceId
, SshCliOpts -> Maybe Text
name :: Maybe Text
, SshCliOpts -> [Text]
passthru :: [Text]
}
deriving stock Int -> SshCliOpts -> ShowS
[SshCliOpts] -> ShowS
SshCliOpts -> String
(Int -> SshCliOpts -> ShowS)
-> (SshCliOpts -> String)
-> ([SshCliOpts] -> ShowS)
-> Show SshCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SshCliOpts -> ShowS
showsPrec :: Int -> SshCliOpts -> ShowS
$cshow :: SshCliOpts -> String
show :: SshCliOpts -> String
$cshowList :: [SshCliOpts] -> ShowS
showList :: [SshCliOpts] -> ShowS
Show
data CopyFileCliOpts = CopyFileCliOpts
{ CopyFileCliOpts -> Maybe CloudyInstanceId
id :: Maybe CloudyInstanceId
, CopyFileCliOpts -> Maybe Text
name :: Maybe Text
, CopyFileCliOpts -> CopyFileDirection
direction :: CopyFileDirection
, CopyFileCliOpts -> Recursive
recursive :: Recursive
, CopyFileCliOpts -> [Text]
filesToCopyArgs :: [Text]
}
deriving stock Int -> CopyFileCliOpts -> ShowS
[CopyFileCliOpts] -> ShowS
CopyFileCliOpts -> String
(Int -> CopyFileCliOpts -> ShowS)
-> (CopyFileCliOpts -> String)
-> ([CopyFileCliOpts] -> ShowS)
-> Show CopyFileCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CopyFileCliOpts -> ShowS
showsPrec :: Int -> CopyFileCliOpts -> ShowS
$cshow :: CopyFileCliOpts -> String
show :: CopyFileCliOpts -> String
$cshowList :: [CopyFileCliOpts] -> ShowS
showList :: [CopyFileCliOpts] -> ShowS
Show
data DestroyCliOpts = DestroyCliOpts
{ DestroyCliOpts -> Maybe CloudyInstanceId
id :: Maybe CloudyInstanceId
, DestroyCliOpts -> Maybe Text
name :: Maybe Text
}
deriving stock Int -> DestroyCliOpts -> ShowS
[DestroyCliOpts] -> ShowS
DestroyCliOpts -> String
(Int -> DestroyCliOpts -> ShowS)
-> (DestroyCliOpts -> String)
-> ([DestroyCliOpts] -> ShowS)
-> Show DestroyCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DestroyCliOpts -> ShowS
showsPrec :: Int -> DestroyCliOpts -> ShowS
$cshow :: DestroyCliOpts -> String
show :: DestroyCliOpts -> String
$cshowList :: [DestroyCliOpts] -> ShowS
showList :: [DestroyCliOpts] -> ShowS
Show
data CopyFileDirection = FromInstanceToLocal | ToInstanceFromLocal
deriving stock Int -> CopyFileDirection -> ShowS
[CopyFileDirection] -> ShowS
CopyFileDirection -> String
(Int -> CopyFileDirection -> ShowS)
-> (CopyFileDirection -> String)
-> ([CopyFileDirection] -> ShowS)
-> Show CopyFileDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CopyFileDirection -> ShowS
showsPrec :: Int -> CopyFileDirection -> ShowS
$cshow :: CopyFileDirection -> String
show :: CopyFileDirection -> String
$cshowList :: [CopyFileDirection] -> ShowS
showList :: [CopyFileDirection] -> ShowS
Show
data Recursive = Recursive | NoRecursive
deriving stock Int -> Recursive -> ShowS
[Recursive] -> ShowS
Recursive -> String
(Int -> Recursive -> ShowS)
-> (Recursive -> String)
-> ([Recursive] -> ShowS)
-> Show Recursive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Recursive -> ShowS
showsPrec :: Int -> Recursive -> ShowS
$cshow :: Recursive -> String
show :: Recursive -> String
$cshowList :: [Recursive] -> ShowS
showList :: [Recursive] -> ShowS
Show
parseCliOpts :: IO CliCmd
parseCliOpts :: IO CliCmd
parseCliOpts = do
[InstanceSetup]
userInstanceSetups <- IO [InstanceSetup]
getUserInstanceSetups
[CloudyInstance]
activeCloudyInstances <- (Connection -> IO [CloudyInstance]) -> IO [CloudyInstance]
forall a. (Connection -> IO a) -> IO a
withCloudyDb Connection -> IO [CloudyInstance]
findAllCloudyInstances
ParserInfo CliCmd -> IO CliCmd
forall a. ParserInfo a -> IO a
execParser ([CloudyInstance] -> [InstanceSetup] -> ParserInfo CliCmd
cliCmdParserInfo [CloudyInstance]
activeCloudyInstances [InstanceSetup]
userInstanceSetups)
cliCmdParserInfo :: [CloudyInstance] -> [InstanceSetup] -> ParserInfo CliCmd
cliCmdParserInfo :: [CloudyInstance] -> [InstanceSetup] -> ParserInfo CliCmd
cliCmdParserInfo [CloudyInstance]
activeCloudyInstances [InstanceSetup]
userInstanceSetups =
Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
( [CloudyInstance] -> [InstanceSetup] -> Parser CliCmd
cliCmdParser [CloudyInstance]
activeCloudyInstances [InstanceSetup]
userInstanceSetups Parser CliCmd -> Parser (CliCmd -> CliCmd) -> Parser CliCmd
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**>
Parser (CliCmd -> CliCmd)
forall a. Parser (a -> a)
helper Parser CliCmd -> Parser (CliCmd -> CliCmd) -> Parser CliCmd
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**>
String -> Parser (CliCmd -> CliCmd)
forall a. String -> Parser (a -> a)
simpleVersioner (Version -> String
showVersion Version
version)
)
( InfoMod CliCmd
forall a. InfoMod a
fullDesc InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
String -> InfoMod CliCmd
forall a. String -> InfoMod a
header String
"cloudy - create, setup, and manage compute instances in various cloud environments"
)
cliCmdParser :: [CloudyInstance] -> [InstanceSetup] -> Parser CliCmd
cliCmdParser :: [CloudyInstance] -> [InstanceSetup] -> Parser CliCmd
cliCmdParser [CloudyInstance]
activeCloudyInstances [InstanceSetup]
userInstanceSetups = Mod CommandFields CliCmd -> Parser CliCmd
forall a. Mod CommandFields a -> Parser a
hsubparser Mod CommandFields CliCmd
subParsers Parser CliCmd -> Parser CliCmd -> Parser CliCmd
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser CliCmd
list
where
subParsers :: Mod CommandFields CliCmd
subParsers =
Mod CommandFields CliCmd
awsCommand Mod CommandFields CliCmd
-> Mod CommandFields CliCmd -> Mod CommandFields CliCmd
forall a. Semigroup a => a -> a -> a
<>
Mod CommandFields CliCmd
scalewayCommand Mod CommandFields CliCmd
-> Mod CommandFields CliCmd -> Mod CommandFields CliCmd
forall a. Semigroup a => a -> a -> a
<>
Mod CommandFields CliCmd
listCommand Mod CommandFields CliCmd
-> Mod CommandFields CliCmd -> Mod CommandFields CliCmd
forall a. Semigroup a => a -> a -> a
<>
Mod CommandFields CliCmd
sshCommand Mod CommandFields CliCmd
-> Mod CommandFields CliCmd -> Mod CommandFields CliCmd
forall a. Semigroup a => a -> a -> a
<>
Mod CommandFields CliCmd
copyFileCommand Mod CommandFields CliCmd
-> Mod CommandFields CliCmd -> Mod CommandFields CliCmd
forall a. Semigroup a => a -> a -> a
<>
Mod CommandFields CliCmd
destroyCommand
awsCommand :: Mod CommandFields CliCmd
awsCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"aws"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
((AwsCliOpts -> CliCmd) -> Parser AwsCliOpts -> Parser CliCmd
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AwsCliOpts -> CliCmd
Aws Parser AwsCliOpts
awsCliOptsParser)
(String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"Run AWS-specific commands")
)
scalewayCommand :: Mod CommandFields CliCmd
scalewayCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"scaleway"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
(ScalewayCliOpts -> CliCmd
Scaleway (ScalewayCliOpts -> CliCmd)
-> Parser ScalewayCliOpts -> Parser CliCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InstanceSetup] -> Parser ScalewayCliOpts
scalewayCliOptsParser [InstanceSetup]
userInstanceSetups)
(String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"Run Scaleway-specific commands")
)
listCommand :: Mod CommandFields CliCmd
listCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"list"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
Parser CliCmd
list
(String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"List currently running compute instances")
)
sshCommand :: Mod CommandFields CliCmd
sshCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"ssh"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
(SshCliOpts -> CliCmd
Ssh (SshCliOpts -> CliCmd) -> Parser SshCliOpts -> Parser CliCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser SshCliOpts
sshCliOptsParser [CloudyInstance]
activeCloudyInstances)
( String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"SSH to currently running compute instances" InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
InfoMod CliCmd
forall a. InfoMod a
noIntersperse InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
(Maybe (Doc AnsiStyle) -> InfoMod CliCmd
forall a. Maybe (Doc AnsiStyle) -> InfoMod a
footerDoc (Maybe (Doc AnsiStyle) -> InfoMod CliCmd)
-> (Doc AnsiStyle -> Maybe (Doc AnsiStyle))
-> Doc AnsiStyle
-> InfoMod CliCmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc AnsiStyle -> Maybe (Doc AnsiStyle)
forall a. a -> Maybe a
Just (Doc AnsiStyle -> InfoMod CliCmd)
-> Doc AnsiStyle -> InfoMod CliCmd
forall a b. (a -> b) -> a -> b
$
[Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc AnsiStyle
"This command internally executes SSH like the following:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ ssh root@12.34.9.9"
, Doc AnsiStyle
""
, Doc AnsiStyle
"Any additional arguments specified to this function will be passed to SSH as-is. \
\For instance, if you run the following command:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ cloudy ssh ls /"
, Doc AnsiStyle
""
, Doc AnsiStyle
"then internally it will execute SSH like the following:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ ssh root@12.34.9.9 ls /"
, Doc AnsiStyle
""
, Doc AnsiStyle
"Note that if you want to pass an option to SSH that matches \
\an option understood by Cloudy, use \"--\" to separate arguments. \
\For instance, if you run the following command:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ cloudy ssh -i pumpkin-dog -- -i ~/.ssh/my_id_rsa"
, Doc AnsiStyle
""
, Doc AnsiStyle
"Cloudy will internally execute the following SSH command against the \
\instance named \"pumpkin-dog\":"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ ssh root@12.34.9.9 -i ~/.ssh/my_id_rsa"
, Doc AnsiStyle
""
, Doc AnsiStyle
"SSH also understands the \"--\" argument, so you may need to \
\combine these depending on what you're trying to do:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ cloudy ssh -i pumpkin-dog -- -i ~/.ssh/my_id_rsa -- ls -i /"
]
)
)
)
copyFileCommand :: Mod CommandFields CliCmd
copyFileCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"copy-file"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
(CopyFileCliOpts -> CliCmd
CopyFile (CopyFileCliOpts -> CliCmd)
-> Parser CopyFileCliOpts -> Parser CliCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser CopyFileCliOpts
copyFileCliOptsParser [CloudyInstance]
activeCloudyInstances)
( String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"Copy files to/from currently running compute instances" InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
InfoMod CliCmd
forall a. InfoMod a
forwardOptions InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
(Maybe (Doc AnsiStyle) -> InfoMod CliCmd
forall a. Maybe (Doc AnsiStyle) -> InfoMod a
footerDoc (Maybe (Doc AnsiStyle) -> InfoMod CliCmd)
-> (Doc AnsiStyle -> Maybe (Doc AnsiStyle))
-> Doc AnsiStyle
-> InfoMod CliCmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc AnsiStyle -> Maybe (Doc AnsiStyle)
forall a. a -> Maybe a
Just (Doc AnsiStyle -> InfoMod CliCmd)
-> Doc AnsiStyle -> InfoMod CliCmd
forall a b. (a -> b) -> a -> b
$
[Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc AnsiStyle
"Here's an example of using this command to copy files from \
\the cloud instance to your local machine:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ cloudy copy-file -i pumpkin-dog --from-instance my-file-remote1 my-file-remote2 ./my-dir-local/"
, Doc AnsiStyle
""
, Doc AnsiStyle
"This internally uses SCP to copy files, running a command \
\like the following:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ scp root@12.34.9.9:my-file-remote1 root@12.34.9.9:my-file-remote2 ./my-dir-local/"
, Doc AnsiStyle
""
, Doc AnsiStyle
"Cloudy will prepend the correct username and IP address to \
\all the remote files. Note that this uses SCP's normal \
\rules for paths, so relative paths will be relative to \
\the user's HOME directory. For instance, in the above \
\command, \"my-file-remote1\" and \"my-file-remote2\" are \
\expected to live in the root user's HOME directory (/root)."
, Doc AnsiStyle
""
, Doc AnsiStyle
"Here's an example of using this command to copy files from \
\your local machine to the cloud instance:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ cloudy copy-file -i pumpkin-dog --to-instance --recursive my-file-local my-dir-local/ my-dir-remote/"
, Doc AnsiStyle
""
, Doc AnsiStyle
"This internally runs a command like the following:"
, Doc AnsiStyle
""
, Doc AnsiStyle
" $ scp -r my-file-local my-dir-local/ root@12.34.9.9:my-dir-remote/"
]
)
)
)
destroyCommand :: Mod CommandFields CliCmd
destroyCommand =
String -> ParserInfo CliCmd -> Mod CommandFields CliCmd
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"destroy"
( Parser CliCmd -> InfoMod CliCmd -> ParserInfo CliCmd
forall a. Parser a -> InfoMod a -> ParserInfo a
info
(DestroyCliOpts -> CliCmd
Destroy (DestroyCliOpts -> CliCmd)
-> Parser DestroyCliOpts -> Parser CliCmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser DestroyCliOpts
destroyCliOptsParser [CloudyInstance]
activeCloudyInstances)
( String -> InfoMod CliCmd
forall a. String -> InfoMod a
progDesc String
"Destroy currently running compute instance" InfoMod CliCmd -> InfoMod CliCmd -> InfoMod CliCmd
forall a. Semigroup a => a -> a -> a
<>
String -> InfoMod CliCmd
forall a. String -> InfoMod a
footer
String
"If neither a CLOUDY_INSTANCE_ID nor a CLOUDY_INSTANCE_NAME is \
\specified, AND there is only a single active Cloudy Instance, \
\it will be used. Otherwise, you must specify either \
\CLOUDY_INSTANCE_ID or CLOUDY_INSTANCE_NAME, but not both. \
\Use `cloudy list` to get a list of all active instances ids \
\and names."
)
)
list :: Parser CliCmd
list = (ListCliOpts -> CliCmd) -> Parser ListCliOpts -> Parser CliCmd
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ListCliOpts -> CliCmd
List Parser ListCliOpts
listCliOptsParser
listCliOptsParser :: Parser ListCliOpts
listCliOptsParser :: Parser ListCliOpts
listCliOptsParser = ListCliOpts -> Parser ListCliOpts
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ListCliOpts
ListCliOpts
sshCliOptsParser :: [CloudyInstance] -> Parser SshCliOpts
sshCliOptsParser :: [CloudyInstance] -> Parser SshCliOpts
sshCliOptsParser [CloudyInstance]
activeCloudyInstances =
Maybe CloudyInstanceId -> Maybe Text -> [Text] -> SshCliOpts
SshCliOpts
(Maybe CloudyInstanceId -> Maybe Text -> [Text] -> SshCliOpts)
-> Parser (Maybe CloudyInstanceId)
-> Parser (Maybe Text -> [Text] -> SshCliOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser (Maybe CloudyInstanceId)
cloudyInstanceIdParser [CloudyInstance]
activeCloudyInstances
Parser (Maybe Text -> [Text] -> SshCliOpts)
-> Parser (Maybe Text) -> Parser ([Text] -> SshCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [CloudyInstance] -> Parser (Maybe Text)
cloudyInstanceNameParser [CloudyInstance]
activeCloudyInstances
Parser ([Text] -> SshCliOpts) -> Parser [Text] -> Parser SshCliOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Text]
passthruArgs
copyFileCliOptsParser :: [CloudyInstance] -> Parser CopyFileCliOpts
copyFileCliOptsParser :: [CloudyInstance] -> Parser CopyFileCliOpts
copyFileCliOptsParser [CloudyInstance]
activeCloudyInstances =
Maybe CloudyInstanceId
-> Maybe Text
-> CopyFileDirection
-> Recursive
-> [Text]
-> CopyFileCliOpts
CopyFileCliOpts
(Maybe CloudyInstanceId
-> Maybe Text
-> CopyFileDirection
-> Recursive
-> [Text]
-> CopyFileCliOpts)
-> Parser (Maybe CloudyInstanceId)
-> Parser
(Maybe Text
-> CopyFileDirection -> Recursive -> [Text] -> CopyFileCliOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser (Maybe CloudyInstanceId)
cloudyInstanceIdParser [CloudyInstance]
activeCloudyInstances
Parser
(Maybe Text
-> CopyFileDirection -> Recursive -> [Text] -> CopyFileCliOpts)
-> Parser (Maybe Text)
-> Parser
(CopyFileDirection -> Recursive -> [Text] -> CopyFileCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [CloudyInstance] -> Parser (Maybe Text)
cloudyInstanceNameParser [CloudyInstance]
activeCloudyInstances
Parser
(CopyFileDirection -> Recursive -> [Text] -> CopyFileCliOpts)
-> Parser CopyFileDirection
-> Parser (Recursive -> [Text] -> CopyFileCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser CopyFileDirection
directionParser
Parser (Recursive -> [Text] -> CopyFileCliOpts)
-> Parser Recursive -> Parser ([Text] -> CopyFileCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Recursive
recursiveParser
Parser ([Text] -> CopyFileCliOpts)
-> Parser [Text] -> Parser CopyFileCliOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser [Text]
copyFilesParser
destroyCliOptsParser :: [CloudyInstance] -> Parser DestroyCliOpts
destroyCliOptsParser :: [CloudyInstance] -> Parser DestroyCliOpts
destroyCliOptsParser [CloudyInstance]
activeCloudyInstances =
Maybe CloudyInstanceId -> Maybe Text -> DestroyCliOpts
DestroyCliOpts
(Maybe CloudyInstanceId -> Maybe Text -> DestroyCliOpts)
-> Parser (Maybe CloudyInstanceId)
-> Parser (Maybe Text -> DestroyCliOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CloudyInstance] -> Parser (Maybe CloudyInstanceId)
cloudyInstanceIdParser [CloudyInstance]
activeCloudyInstances
Parser (Maybe Text -> DestroyCliOpts)
-> Parser (Maybe Text) -> Parser DestroyCliOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [CloudyInstance] -> Parser (Maybe Text)
cloudyInstanceNameParser [CloudyInstance]
activeCloudyInstances
cloudyInstanceIdParser :: [CloudyInstance] -> Parser (Maybe CloudyInstanceId)
cloudyInstanceIdParser :: [CloudyInstance] -> Parser (Maybe CloudyInstanceId)
cloudyInstanceIdParser [CloudyInstance]
activeCloudyInstances = (Int64 -> CloudyInstanceId)
-> Maybe Int64 -> Maybe CloudyInstanceId
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> CloudyInstanceId
CloudyInstanceId (Maybe Int64 -> Maybe CloudyInstanceId)
-> Parser (Maybe Int64) -> Parser (Maybe CloudyInstanceId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe Int64)
innerParser
where
innerParser :: Parser (Maybe Int64)
innerParser :: Parser (Maybe Int64)
innerParser =
Parser Int64 -> Parser (Maybe Int64)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Int64 -> Parser (Maybe Int64))
-> Parser Int64 -> Parser (Maybe Int64)
forall a b. (a -> b) -> a -> b
$
ReadM Int64 -> Mod OptionFields Int64 -> Parser Int64
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
ReadM Int64
forall a. Read a => ReadM a
auto
( String -> Mod OptionFields Int64
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"id" Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields Int64
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'i' Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int64
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"CLOUDY_INSTANCE_ID" Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int64
forall (f :: * -> *) a. String -> Mod f a
help String
"Cloudy instance ID to operate on." Mod OptionFields Int64
-> Mod OptionFields Int64 -> Mod OptionFields Int64
forall a. Semigroup a => a -> a -> a
<>
[String] -> Mod OptionFields Int64
forall (f :: * -> *) a. HasCompleter f => [String] -> Mod f a
completeWith ((CloudyInstance -> String) -> [CloudyInstance] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CloudyInstance
inst -> Int64 -> String
forall a. Show a => a -> String
show (Int64 -> String) -> Int64 -> String
forall a b. (a -> b) -> a -> b
$ CloudyInstanceId -> Int64
unCloudyInstanceId CloudyInstance
inst.id) [CloudyInstance]
activeCloudyInstances)
)
cloudyInstanceNameParser :: [CloudyInstance] -> Parser (Maybe Text)
cloudyInstanceNameParser :: [CloudyInstance] -> Parser (Maybe Text)
cloudyInstanceNameParser [CloudyInstance]
activeCloudyInstances =
Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Text -> Parser (Maybe Text))
-> Parser Text -> Parser (Maybe Text)
forall a b. (a -> b) -> a -> b
$
Mod OptionFields Text -> Parser Text
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"name" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'n' Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"CLOUDY_INSTANCE_NAME" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
help String
"Cloudy instance name to operate on." Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
[String] -> Mod OptionFields Text
forall (f :: * -> *) a. HasCompleter f => [String] -> Mod f a
completeWith ((CloudyInstance -> String) -> [CloudyInstance] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CloudyInstance
inst -> Text -> String
unpack CloudyInstance
inst.name) [CloudyInstance]
activeCloudyInstances)
)
passthruArgs :: Parser [Text]
passthruArgs :: Parser [Text]
passthruArgs =
Parser Text -> Parser [Text]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parser Text -> Parser [Text]) -> Parser Text -> Parser [Text]
forall a b. (a -> b) -> a -> b
$
Mod ArgumentFields Text -> Parser Text
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument
( String -> Mod ArgumentFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"SSH_ARG..." Mod ArgumentFields Text
-> Mod ArgumentFields Text -> Mod ArgumentFields Text
forall a. Semigroup a => a -> a -> a
<>
String -> Mod ArgumentFields Text
forall (f :: * -> *) a. String -> Mod f a
help String
"Arguments to passthru to SSH"
)
copyFilesParser :: Parser [Text]
copyFilesParser :: Parser [Text]
copyFilesParser =
Parser Text -> Parser [Text]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Parser Text -> Parser [Text]) -> Parser Text -> Parser [Text]
forall a b. (a -> b) -> a -> b
$
Mod ArgumentFields Text -> Parser Text
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument
( String -> Mod ArgumentFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"FILE..." Mod ArgumentFields Text
-> Mod ArgumentFields Text -> Mod ArgumentFields Text
forall a. Semigroup a => a -> a -> a
<>
String -> Mod ArgumentFields Text
forall (f :: * -> *) a. String -> Mod f a
help String
"File names to copy to/from"
)
directionParser :: Parser CopyFileDirection
directionParser :: Parser CopyFileDirection
directionParser =
let fromInstanceFlag :: Parser CopyFileDirection
fromInstanceFlag =
CopyFileDirection
-> Mod FlagFields CopyFileDirection -> Parser CopyFileDirection
forall a. a -> Mod FlagFields a -> Parser a
flag'
CopyFileDirection
FromInstanceToLocal
( String -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"from-instance" Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f' Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. String -> Mod f a
help String
"Copy files FROM CLOUD INSTANCE to your local machine"
)
toInstanceFlag :: Parser CopyFileDirection
toInstanceFlag =
CopyFileDirection
-> Mod FlagFields CopyFileDirection -> Parser CopyFileDirection
forall a. a -> Mod FlagFields a -> Parser a
flag'
CopyFileDirection
ToInstanceFromLocal
( String -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"to-instance" Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
't' Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
-> Mod FlagFields CopyFileDirection
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields CopyFileDirection
forall (f :: * -> *) a. String -> Mod f a
help String
"Copy files from your local machine TO CLOUD INSTANCE"
)
in Parser CopyFileDirection
fromInstanceFlag Parser CopyFileDirection
-> Parser CopyFileDirection -> Parser CopyFileDirection
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser CopyFileDirection
toInstanceFlag
recursiveParser :: Parser Recursive
recursiveParser :: Parser Recursive
recursiveParser =
Recursive
-> Recursive -> Mod FlagFields Recursive -> Parser Recursive
forall a. a -> a -> Mod FlagFields a -> Parser a
flag
Recursive
NoRecursive
Recursive
Recursive
( String -> Mod FlagFields Recursive
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"recursive" Mod FlagFields Recursive
-> Mod FlagFields Recursive -> Mod FlagFields Recursive
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Recursive
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r' Mod FlagFields Recursive
-> Mod FlagFields Recursive -> Mod FlagFields Recursive
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Recursive
forall (f :: * -> *) a. String -> Mod f a
help String
"Recursively copy entire directories"
)