{-# LANGUAGE NoImplicitPrelude #-}
module Refurb.Cli where
import ClassyPrelude
import Composite.Record ((:->)(Val))
import qualified Options.Applicative as OA
import Refurb.Store (FQualifiedKey)
newtype GoNoGo = GoNoGo Bool deriving (GoNoGo -> GoNoGo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GoNoGo -> GoNoGo -> Bool
$c/= :: GoNoGo -> GoNoGo -> Bool
== :: GoNoGo -> GoNoGo -> Bool
$c== :: GoNoGo -> GoNoGo -> Bool
Eq, Int -> GoNoGo -> ShowS
[GoNoGo] -> ShowS
GoNoGo -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GoNoGo] -> ShowS
$cshowList :: [GoNoGo] -> ShowS
show :: GoNoGo -> FilePath
$cshow :: GoNoGo -> FilePath
showsPrec :: Int -> GoNoGo -> ShowS
$cshowsPrec :: Int -> GoNoGo -> ShowS
Show)
newtype PreMigrationBackup = PreMigrationBackup FilePath deriving (PreMigrationBackup -> PreMigrationBackup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreMigrationBackup -> PreMigrationBackup -> Bool
$c/= :: PreMigrationBackup -> PreMigrationBackup -> Bool
== :: PreMigrationBackup -> PreMigrationBackup -> Bool
$c== :: PreMigrationBackup -> PreMigrationBackup -> Bool
Eq, Int -> PreMigrationBackup -> ShowS
[PreMigrationBackup] -> ShowS
PreMigrationBackup -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PreMigrationBackup] -> ShowS
$cshowList :: [PreMigrationBackup] -> ShowS
show :: PreMigrationBackup -> FilePath
$cshow :: PreMigrationBackup -> FilePath
showsPrec :: Int -> PreMigrationBackup -> ShowS
$cshowsPrec :: Int -> PreMigrationBackup -> ShowS
Show)
newtype InstallSeedData = InstallSeedData Bool deriving (InstallSeedData -> InstallSeedData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstallSeedData -> InstallSeedData -> Bool
$c/= :: InstallSeedData -> InstallSeedData -> Bool
== :: InstallSeedData -> InstallSeedData -> Bool
$c== :: InstallSeedData -> InstallSeedData -> Bool
Eq, Int -> InstallSeedData -> ShowS
[InstallSeedData] -> ShowS
InstallSeedData -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [InstallSeedData] -> ShowS
$cshowList :: [InstallSeedData] -> ShowS
show :: InstallSeedData -> FilePath
$cshow :: InstallSeedData -> FilePath
showsPrec :: Int -> InstallSeedData -> ShowS
$cshowsPrec :: Int -> InstallSeedData -> ShowS
Show)
data Command
= CommandMigrate GoNoGo (Maybe PreMigrationBackup) InstallSeedData
| CommandShowLog
| CommandShowMigration FQualifiedKey
| CommandBackup FilePath
deriving (Command -> Command -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c== :: Command -> Command -> Bool
Eq, Int -> Command -> ShowS
[Command] -> ShowS
Command -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> FilePath
$cshow :: Command -> FilePath
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show)
commandMigrateParser :: OA.ParserInfo Command
commandMigrateParser :: ParserInfo Command
commandMigrateParser =
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info
(
GoNoGo -> Maybe PreMigrationBackup -> InstallSeedData -> Command
CommandMigrate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( Bool -> GoNoGo
GoNoGo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
OA.switch
( forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"execute"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'e'
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"Actually run migrations. Without this switch the migrations to run will be logged but none of them executed."
)
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ( forall a. ReadM a -> Mod OptionFields a -> Parser a
OA.option (forall a. a -> Maybe a
Just forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. FilePath -> PreMigrationBackup
PreMigrationBackup forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => ReadM a
OA.auto)
( forall (f :: * -> *) a. HasValue f => a -> Mod f a
OA.value forall a. Maybe a
Nothing
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"backup-first"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'b'
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
OA.metavar FilePath
"BACKUP-FILE"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"Back up the database before applying migrations. Has no effect without --execute."
)
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ( Bool -> InstallSeedData
InstallSeedData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
OA.switch
( forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"seed"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
's'
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"Apply seed scripts in addition to schema migrations. Not available on prod databases."
)
)
)
( forall a. FilePath -> InfoMod a
OA.progDesc FilePath
"Apply migrations to the database, or see which ones would be applied" )
commandShowLogParser :: OA.ParserInfo Command
commandShowLogParser :: ParserInfo Command
commandShowLogParser =
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info
(
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandShowLog
)
( forall a. FilePath -> InfoMod a
OA.progDesc FilePath
"Show migrations along with their status in the database" )
commandShowMigrationParser :: OA.ParserInfo Command
commandShowMigrationParser :: ParserInfo Command
commandShowMigrationParser =
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info
(
FQualifiedKey -> Command
CommandShowMigration
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (s :: Symbol) a. a -> s :-> a
Val forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall seq. IsSequence seq => [Element seq] -> seq
pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. IsString s => Mod ArgumentFields s -> Parser s
OA.strArgument (forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
OA.metavar FilePath
"MIGRATION-KEY"))
)
( forall a. FilePath -> InfoMod a
OA.progDesc FilePath
"Show status of and log details for a particular migration" )
commandBackupParser :: OA.ParserInfo Command
commandBackupParser :: ParserInfo Command
commandBackupParser =
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info
(
FilePath -> Command
CommandBackup
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. IsString s => Mod ArgumentFields s -> Parser s
OA.strArgument (forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
OA.metavar FilePath
"BACKUP-FILE")
)
( forall a. FilePath -> InfoMod a
OA.progDesc FilePath
"Back up the database" )
data Opts = Opts
{ Opts -> Bool
debug :: Bool
, Opts -> Bool
colorize :: Bool
, Opts -> FilePath
configFile :: FilePath
, Opts -> Command
command :: Command
}
optsParser :: OA.ParserInfo Opts
optsParser :: ParserInfo Opts
optsParser =
forall a. Parser a -> InfoMod a -> ParserInfo a
OA.info
(
forall a. Parser (a -> a)
OA.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (
Bool -> Bool -> FilePath -> Command -> Opts
Opts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
OA.switch
( forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"debug"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'd'
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"Turn on debug diagnostic logging"
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
OA.switch (forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"no-color" forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"disable ANSI colorization"))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall s. IsString s => Mod OptionFields s -> Parser s
OA.strOption
( forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
OA.long FilePath
"config"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => Char -> Mod f a
OA.short Char
'c'
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
OA.metavar FilePath
"SERVER-CONFIG"
forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. FilePath -> Mod f a
OA.help FilePath
"Path to server config file to read database connection information from"
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Mod CommandFields a -> Parser a
OA.hsubparser
( forall a. FilePath -> ParserInfo a -> Mod CommandFields a
OA.command FilePath
"migrate" ParserInfo Command
commandMigrateParser
forall a. Semigroup a => a -> a -> a
<> forall a. FilePath -> ParserInfo a -> Mod CommandFields a
OA.command FilePath
"show-log" ParserInfo Command
commandShowLogParser
forall a. Semigroup a => a -> a -> a
<> forall a. FilePath -> ParserInfo a -> Mod CommandFields a
OA.command FilePath
"show-migration" ParserInfo Command
commandShowMigrationParser
forall a. Semigroup a => a -> a -> a
<> forall a. FilePath -> ParserInfo a -> Mod CommandFields a
OA.command FilePath
"backup" ParserInfo Command
commandBackupParser
)
)
)
( forall a. InfoMod a
OA.fullDesc
forall a. Semigroup a => a -> a -> a
<> forall a. FilePath -> InfoMod a
OA.header FilePath
"Maintain server database"
)