{-# LANGUAGE OverloadedRecordDot #-}
module Cloudy.Cli.Scaleway where
import Cloudy.Cli.Utils (maybeOpt)
import Cloudy.InstanceSetup (builtInInstanceSetups)
import Cloudy.InstanceSetup.Types (InstanceSetup (..), InstanceSetupData (..))
import Control.Applicative (optional)
import Data.Text (Text, unpack)
import Options.Applicative (Parser, command, info, progDesc, hsubparser, strOption, long, short, metavar, option, help, value, showDefault, maybeReader, switch, auto, footerDoc, completeWith)
import Options.Applicative.Help (vsep, Doc)
import Data.String (IsString(fromString))
import Cloudy.Scaleway (allScalewayZones, zoneToText)
data ScalewayCliOpts
= ScalewayCreate ScalewayCreateCliOpts
| ScalewayListInstanceTypes ScalewayListInstanceTypesCliOpts
| ScalewayListImages ScalewayListImagesCliOpts
deriving stock Int -> ScalewayCliOpts -> ShowS
[ScalewayCliOpts] -> ShowS
ScalewayCliOpts -> String
(Int -> ScalewayCliOpts -> ShowS)
-> (ScalewayCliOpts -> String)
-> ([ScalewayCliOpts] -> ShowS)
-> Show ScalewayCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalewayCliOpts -> ShowS
showsPrec :: Int -> ScalewayCliOpts -> ShowS
$cshow :: ScalewayCliOpts -> String
show :: ScalewayCliOpts -> String
$cshowList :: [ScalewayCliOpts] -> ShowS
showList :: [ScalewayCliOpts] -> ShowS
Show
data ScalewayCreateCliOpts = ScalewayCreateCliOpts
{ ScalewayCreateCliOpts -> Maybe Text
zone :: Maybe Text
, ScalewayCreateCliOpts -> Maybe Text
instanceType :: Maybe Text
, ScalewayCreateCliOpts -> Int
volumeSizeGb :: Int
, ScalewayCreateCliOpts -> Maybe Text
imageId :: Maybe Text
, ScalewayCreateCliOpts -> Maybe Text
instanceSetup :: Maybe Text
}
deriving stock Int -> ScalewayCreateCliOpts -> ShowS
[ScalewayCreateCliOpts] -> ShowS
ScalewayCreateCliOpts -> String
(Int -> ScalewayCreateCliOpts -> ShowS)
-> (ScalewayCreateCliOpts -> String)
-> ([ScalewayCreateCliOpts] -> ShowS)
-> Show ScalewayCreateCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalewayCreateCliOpts -> ShowS
showsPrec :: Int -> ScalewayCreateCliOpts -> ShowS
$cshow :: ScalewayCreateCliOpts -> String
show :: ScalewayCreateCliOpts -> String
$cshowList :: [ScalewayCreateCliOpts] -> ShowS
showList :: [ScalewayCreateCliOpts] -> ShowS
Show
data ScalewayListInstanceTypesCliOpts = ScalewayListInstanceTypesCliOpts
{ ScalewayListInstanceTypesCliOpts -> Maybe Text
zone :: Maybe Text
}
deriving stock Int -> ScalewayListInstanceTypesCliOpts -> ShowS
[ScalewayListInstanceTypesCliOpts] -> ShowS
ScalewayListInstanceTypesCliOpts -> String
(Int -> ScalewayListInstanceTypesCliOpts -> ShowS)
-> (ScalewayListInstanceTypesCliOpts -> String)
-> ([ScalewayListInstanceTypesCliOpts] -> ShowS)
-> Show ScalewayListInstanceTypesCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalewayListInstanceTypesCliOpts -> ShowS
showsPrec :: Int -> ScalewayListInstanceTypesCliOpts -> ShowS
$cshow :: ScalewayListInstanceTypesCliOpts -> String
show :: ScalewayListInstanceTypesCliOpts -> String
$cshowList :: [ScalewayListInstanceTypesCliOpts] -> ShowS
showList :: [ScalewayListInstanceTypesCliOpts] -> ShowS
Show
data ScalewayListImagesCliOpts = ScalewayListImagesCliOpts
{ ScalewayListImagesCliOpts -> Maybe Text
zone :: Maybe Text
, ScalewayListImagesCliOpts -> Text
arch :: Text
, ScalewayListImagesCliOpts -> Maybe Text
nameFilter :: Maybe Text
, ScalewayListImagesCliOpts -> Bool
allVersions :: Bool
}
deriving stock Int -> ScalewayListImagesCliOpts -> ShowS
[ScalewayListImagesCliOpts] -> ShowS
ScalewayListImagesCliOpts -> String
(Int -> ScalewayListImagesCliOpts -> ShowS)
-> (ScalewayListImagesCliOpts -> String)
-> ([ScalewayListImagesCliOpts] -> ShowS)
-> Show ScalewayListImagesCliOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalewayListImagesCliOpts -> ShowS
showsPrec :: Int -> ScalewayListImagesCliOpts -> ShowS
$cshow :: ScalewayListImagesCliOpts -> String
show :: ScalewayListImagesCliOpts -> String
$cshowList :: [ScalewayListImagesCliOpts] -> ShowS
showList :: [ScalewayListImagesCliOpts] -> ShowS
Show
scalewayCliOptsParser :: [InstanceSetup] -> Parser ScalewayCliOpts
scalewayCliOptsParser :: [InstanceSetup] -> Parser ScalewayCliOpts
scalewayCliOptsParser [InstanceSetup]
userInstanceSetups = Mod CommandFields ScalewayCliOpts -> Parser ScalewayCliOpts
forall a. Mod CommandFields a -> Parser a
hsubparser Mod CommandFields ScalewayCliOpts
subParsers
where
subParsers :: Mod CommandFields ScalewayCliOpts
subParsers = Mod CommandFields ScalewayCliOpts
createCommand Mod CommandFields ScalewayCliOpts
-> Mod CommandFields ScalewayCliOpts
-> Mod CommandFields ScalewayCliOpts
forall a. Semigroup a => a -> a -> a
<> Mod CommandFields ScalewayCliOpts
listInstanceTypesCommand Mod CommandFields ScalewayCliOpts
-> Mod CommandFields ScalewayCliOpts
-> Mod CommandFields ScalewayCliOpts
forall a. Semigroup a => a -> a -> a
<> Mod CommandFields ScalewayCliOpts
listImagesCommand
createCommand :: Mod CommandFields ScalewayCliOpts
createCommand =
String
-> ParserInfo ScalewayCliOpts -> Mod CommandFields ScalewayCliOpts
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"create"
( Parser ScalewayCliOpts
-> InfoMod ScalewayCliOpts -> ParserInfo ScalewayCliOpts
forall a. Parser a -> InfoMod a -> ParserInfo a
info
(ScalewayCreateCliOpts -> ScalewayCliOpts
ScalewayCreate (ScalewayCreateCliOpts -> ScalewayCliOpts)
-> Parser ScalewayCreateCliOpts -> Parser ScalewayCliOpts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InstanceSetup] -> Parser ScalewayCreateCliOpts
scalewayCreateCliOptsParser [InstanceSetup]
userInstanceSetups)
( String -> InfoMod ScalewayCliOpts
forall a. String -> InfoMod a
progDesc String
"Create a new compute instance in Scaleway" InfoMod ScalewayCliOpts
-> InfoMod ScalewayCliOpts -> InfoMod ScalewayCliOpts
forall a. Semigroup a => a -> a -> a
<>
(Maybe Doc -> InfoMod ScalewayCliOpts
forall a. Maybe Doc -> InfoMod a
footerDoc (Maybe Doc -> InfoMod ScalewayCliOpts)
-> (Doc -> Maybe Doc) -> Doc -> InfoMod ScalewayCliOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> InfoMod ScalewayCliOpts) -> Doc -> InfoMod ScalewayCliOpts
forall a b. (a -> b) -> a -> b
$
[Doc] -> Doc
forall ann. [Doc ann] -> Doc ann
vsep
( [ Doc
"You can use the --instance-setup option to configure which \
\instance setup script is used to setup the instance after \
\boot. The instance setup scripts generally have a \
\`cloud-init` section, which specifies the actual cloud-init \
\setup to use."
, Doc
""
, Doc
"Default instance-setup scripts builtin to Cloudy:"
, Doc
""
] [Doc] -> [Doc] -> [Doc]
forall a. Semigroup a => a -> a -> a
<>
(InstanceSetup -> Doc) -> [InstanceSetup] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InstanceSetup -> Doc
instanceSetupToDoc [InstanceSetup]
builtInInstanceSetups [Doc] -> [Doc] -> [Doc]
forall a. Semigroup a => a -> a -> a
<>
[ Doc
""
, Doc
"User-defined instance-setup scripts in ~/.config/cloudy/instance-setups/:"
, Doc
""
] [Doc] -> [Doc] -> [Doc]
forall a. Semigroup a => a -> a -> a
<>
case [InstanceSetup]
userInstanceSetups of
[] -> [Doc
"(none exist)"]
[InstanceSetup]
_ -> (InstanceSetup -> Doc) -> [InstanceSetup] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap InstanceSetup -> Doc
instanceSetupToDoc [InstanceSetup]
userInstanceSetups
)
)
)
)
listInstanceTypesCommand :: Mod CommandFields ScalewayCliOpts
listInstanceTypesCommand =
String
-> ParserInfo ScalewayCliOpts -> Mod CommandFields ScalewayCliOpts
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"list-instance-types"
( Parser ScalewayCliOpts
-> InfoMod ScalewayCliOpts -> ParserInfo ScalewayCliOpts
forall a. Parser a -> InfoMod a -> ParserInfo a
info
((ScalewayListInstanceTypesCliOpts -> ScalewayCliOpts)
-> Parser ScalewayListInstanceTypesCliOpts
-> Parser ScalewayCliOpts
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScalewayListInstanceTypesCliOpts -> ScalewayCliOpts
ScalewayListInstanceTypes Parser ScalewayListInstanceTypesCliOpts
scalewayListInstanceTypesCliOptsParser)
(String -> InfoMod ScalewayCliOpts
forall a. String -> InfoMod a
progDesc String
"List all instance types in Scaleway")
)
listImagesCommand :: Mod CommandFields ScalewayCliOpts
listImagesCommand =
String
-> ParserInfo ScalewayCliOpts -> Mod CommandFields ScalewayCliOpts
forall a. String -> ParserInfo a -> Mod CommandFields a
command
String
"list-images"
( Parser ScalewayCliOpts
-> InfoMod ScalewayCliOpts -> ParserInfo ScalewayCliOpts
forall a. Parser a -> InfoMod a -> ParserInfo a
info
((ScalewayListImagesCliOpts -> ScalewayCliOpts)
-> Parser ScalewayListImagesCliOpts -> Parser ScalewayCliOpts
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ScalewayListImagesCliOpts -> ScalewayCliOpts
ScalewayListImages Parser ScalewayListImagesCliOpts
scalewayListImagesCliOptsParser)
(String -> InfoMod ScalewayCliOpts
forall a. String -> InfoMod a
progDesc String
"List available images in Scaleway")
)
instanceSetupToDoc :: InstanceSetup -> Doc
instanceSetupToDoc :: InstanceSetup -> Doc
instanceSetupToDoc InstanceSetup
instanceSetup =
Doc
" - " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
forall a. IsString a => String -> a
fromString (Text -> String
unpack InstanceSetup
instanceSetup.name) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<>
Doc
" -- " Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
forall a. IsString a => String -> a
fromString (Text -> String
unpack InstanceSetup
instanceSetup.instanceSetupData.shortDescription)
scalewayCreateCliOptsParser :: [InstanceSetup] -> Parser ScalewayCreateCliOpts
scalewayCreateCliOptsParser :: [InstanceSetup] -> Parser ScalewayCreateCliOpts
scalewayCreateCliOptsParser [InstanceSetup]
userInstanceSetups =
Maybe Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> ScalewayCreateCliOpts
ScalewayCreateCliOpts
(Maybe Text
-> Maybe Text
-> Int
-> Maybe Text
-> Maybe Text
-> ScalewayCreateCliOpts)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Int -> Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe Text)
zoneParser
Parser
(Maybe Text
-> Int -> Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
-> Parser (Maybe Text)
-> Parser
(Int -> Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Text)
instanceTypeParser
Parser (Int -> Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
-> Parser Int
-> Parser (Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
volumeSizeGbParser
Parser (Maybe Text -> Maybe Text -> ScalewayCreateCliOpts)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> ScalewayCreateCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Text)
imageIdParser
Parser (Maybe Text -> ScalewayCreateCliOpts)
-> Parser (Maybe Text) -> Parser ScalewayCreateCliOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [InstanceSetup] -> Parser (Maybe Text)
instanceSetupParser [InstanceSetup]
userInstanceSetups
scalewayListInstanceTypesCliOptsParser :: Parser ScalewayListInstanceTypesCliOpts
scalewayListInstanceTypesCliOptsParser :: Parser ScalewayListInstanceTypesCliOpts
scalewayListInstanceTypesCliOptsParser = Maybe Text -> ScalewayListInstanceTypesCliOpts
ScalewayListInstanceTypesCliOpts (Maybe Text -> ScalewayListInstanceTypesCliOpts)
-> Parser (Maybe Text) -> Parser ScalewayListInstanceTypesCliOpts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe Text)
zoneParser
scalewayListImagesCliOptsParser :: Parser ScalewayListImagesCliOpts
scalewayListImagesCliOptsParser :: Parser ScalewayListImagesCliOpts
scalewayListImagesCliOptsParser =
Maybe Text
-> Text -> Maybe Text -> Bool -> ScalewayListImagesCliOpts
ScalewayListImagesCliOpts
(Maybe Text
-> Text -> Maybe Text -> Bool -> ScalewayListImagesCliOpts)
-> Parser (Maybe Text)
-> Parser (Text -> Maybe Text -> Bool -> ScalewayListImagesCliOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe Text)
zoneParser
Parser (Text -> Maybe Text -> Bool -> ScalewayListImagesCliOpts)
-> Parser Text
-> Parser (Maybe Text -> Bool -> ScalewayListImagesCliOpts)
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
archParser
Parser (Maybe Text -> Bool -> ScalewayListImagesCliOpts)
-> Parser (Maybe Text)
-> Parser (Bool -> ScalewayListImagesCliOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Text)
nameFilterParser
Parser (Bool -> ScalewayListImagesCliOpts)
-> Parser Bool -> Parser ScalewayListImagesCliOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
allVersionsParser
zoneParser :: Parser (Maybe Text)
zoneParser :: Parser (Maybe Text)
zoneParser =
String
-> Text
-> (Mod OptionFields Text -> Parser Text)
-> Mod OptionFields Text
-> Parser (Maybe Text)
forall a (f :: * -> *).
Show a =>
String -> a -> (Mod f a -> Parser a) -> Mod f a -> Parser (Maybe a)
maybeOpt
String
"Scaleway zone in which to create the new instance"
Text
"nl-ams-1"
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
"zone" 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
'z' 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
"ZONE" 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 (Text -> String
unpack (Text -> String) -> (Zone -> Text) -> Zone -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Zone -> Text
zoneToText (Zone -> String) -> [Zone] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Zone]
allScalewayZones)
)
instanceTypeParser :: Parser (Maybe Text)
instanceTypeParser :: Parser (Maybe Text)
instanceTypeParser =
String
-> Text
-> (Mod OptionFields Text -> Parser Text)
-> Mod OptionFields Text
-> Parser (Maybe Text)
forall a (f :: * -> *).
Show a =>
String -> a -> (Mod f a -> Parser a) -> Mod f a -> Parser (Maybe a)
maybeOpt
String
"Scaleway instance type (use `cloudy scaleway list-instance-types` command to get list of all instance types)"
Text
"PLAY2-NANO"
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
"instance-type" 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
'c' 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
"INSTANCE_TYPE"
)
archParser :: Parser Text
archParser :: Parser Text
archParser =
ReadM Text -> Mod OptionFields Text -> Parser Text
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
((String -> Maybe Text) -> ReadM Text
forall a. (String -> Maybe a) -> ReadM a
maybeReader String -> Maybe Text
archReader)
( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"arch" 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
'a' 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
"ARCH" 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
"Architecture of image. Possiblities: \"x86_64\", \"arm\", or \"arm64\"" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
Text -> Mod OptionFields Text
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Text
"x86_64" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields Text
forall a (f :: * -> *). Show a => Mod f a
showDefault 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 [String
"x86_64", String
"arm", String
"arm64"]
)
where
archReader :: String -> Maybe Text
archReader :: String -> Maybe Text
archReader = \case
String
"x86_64" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"x86_64"
String
"arm" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"arm"
String
"arm64" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"arm64"
String
_ -> Maybe Text
forall a. Maybe a
Nothing
nameFilterParser :: Parser (Maybe Text)
nameFilterParser :: Parser (Maybe Text)
nameFilterParser =
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-filter" 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
"NAME_FILTER" 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
"Only show images whose name contains this value, case-insensitive (default: no filter)"
)
allVersionsParser :: Parser Bool
allVersionsParser :: Parser Bool
allVersionsParser =
Mod FlagFields Bool -> Parser Bool
switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"all-versions" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'a' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"List all versions of each image. By default, only show the latest version for each image name."
)
volumeSizeGbParser :: Parser Int
volumeSizeGbParser :: Parser Int
volumeSizeGbParser =
ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
ReadM Int
forall a. Read a => ReadM a
auto
( String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"volume-size" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
's' Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"VOLUME_SIZE" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
help String
"Size of the root volume in GBs" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
50 Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
imageIdParser :: Parser (Maybe Text)
imageIdParser :: Parser (Maybe Text)
imageIdParser =
String
-> Text
-> (Mod OptionFields Text -> Parser Text)
-> Mod OptionFields Text
-> Parser (Maybe Text)
forall a (f :: * -> *).
Show a =>
String -> a -> (Mod f a -> Parser a) -> Mod f a -> Parser (Maybe a)
maybeOpt
String
"Scaleway image ID (use `cloudy scaleway list-images` command to get list of possible image IDs). Also can be image label, like \"ubuntu_noble\" (TODO: implement market api to return list of possible labels)"
Text
"ubuntu_noble"
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
"image-id" 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
'i' 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
"IMAGE_ID"
)
instanceSetupParser :: [InstanceSetup] -> Parser (Maybe Text)
instanceSetupParser :: [InstanceSetup] -> Parser (Maybe Text)
instanceSetupParser [InstanceSetup]
userInstanceSetups =
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
"instance-setup" 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
't' 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
"INSTANCE_SETUP" 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
"Name of the instance-setup to use when booting the image. (default: do no instance setup)" 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
((InstanceSetup -> String) -> [InstanceSetup] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\InstanceSetup
instSetup -> Text -> String
unpack InstanceSetup
instSetup.name) ([InstanceSetup]
userInstanceSetups [InstanceSetup] -> [InstanceSetup] -> [InstanceSetup]
forall a. Semigroup a => a -> a -> a
<> [InstanceSetup]
builtInInstanceSetups))
)