{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

module System.Hapistrano.Config
  ( Config (..)
  , CopyThing (..)
  , Target (..))
where

import           Control.Applicative        ((<|>))
import           Data.Aeson
import           Data.Function              (on)
import           Data.List                  (nubBy)
import           Data.Maybe                 (maybeToList)
import           Data.Yaml
import           Numeric.Natural
import           Path
import           System.Hapistrano.Commands
import           System.Hapistrano.Types    (Shell(..),
                                             ReleaseFormat (..),
                                             Source(..),
                                             TargetSystem (..))

-- | Hapistrano configuration typically loaded from @hap.yaml@ file.

data Config = Config
  { Config -> Path Abs Dir
configDeployPath     :: !(Path Abs Dir)
    -- ^ Top-level deploy directory on target machine
  , Config -> [Target]
configHosts          :: ![Target]
    -- ^ Hosts\/ports\/shell\/ssh args to deploy to. If empty, localhost will be assumed.
  , Config -> Source
configSource         :: !Source
    -- ^ Location of the 'Source' that contains the code to deploy
  , Config -> Maybe GenericCommand
configRestartCommand :: !(Maybe GenericCommand)
    -- ^ The command to execute when switching to a different release
    -- (usually after a deploy or rollback).
  , Config -> Maybe [GenericCommand]
configBuildScript    :: !(Maybe [GenericCommand])
    -- ^ Build script to execute to build the project
  , Config -> [CopyThing]
configCopyFiles      :: ![CopyThing]
    -- ^ Collection of files to copy over to target machine before building
  , Config -> [CopyThing]
configCopyDirs       :: ![CopyThing]
    -- ^ Collection of directories to copy over to target machine before building
  , Config -> [FilePath]
configLinkedFiles      :: ![FilePath]
    -- ^ Collection of files to link from each release to _shared_
  , Config -> [FilePath]
configLinkedDirs       :: ![FilePath]
    -- ^ Collection of directories to link from each release to _shared_
  , Config -> Bool
configVcAction       :: !Bool
  -- ^ Perform version control related actions. By default, it's assumed to be True.
  , Config -> Maybe [GenericCommand]
configRunLocally     :: !(Maybe [GenericCommand])
  -- ^ Perform a series of commands on the local machine before communication
  -- with target server starts
  , Config -> TargetSystem
configTargetSystem   :: !TargetSystem
  -- ^ Optional parameter to specify the target system. It's GNU/Linux by
  -- default
  , Config -> Maybe ReleaseFormat
configReleaseFormat  :: !(Maybe ReleaseFormat)
  -- ^ The release timestamp format, the '--release-format' argument passed via
  -- the CLI takes precedence over this value. If neither CLI or configuration
  -- file value is specified, it defaults to short
  , Config -> Maybe Natural
configKeepReleases   :: !(Maybe Natural)
  -- ^ The number of releases to keep, the '--keep-releases' argument passed via
  -- the CLI takes precedence over this value. If neither CLI or configuration
  -- file value is specified, it defaults to 5
  , Config -> Maybe (Path Rel Dir)
configWorkingDir :: !(Maybe (Path Rel Dir))
  } deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: Config -> Config -> Bool
Eq, Eq Config
Eq Config
-> (Config -> Config -> Ordering)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Config)
-> (Config -> Config -> Config)
-> Ord Config
Config -> Config -> Bool
Config -> Config -> Ordering
Config -> Config -> Config
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 :: Config -> Config -> Config
$cmin :: Config -> Config -> Config
max :: Config -> Config -> Config
$cmax :: Config -> Config -> Config
>= :: Config -> Config -> Bool
$c>= :: Config -> Config -> Bool
> :: Config -> Config -> Bool
$c> :: Config -> Config -> Bool
<= :: Config -> Config -> Bool
$c<= :: Config -> Config -> Bool
< :: Config -> Config -> Bool
$c< :: Config -> Config -> Bool
compare :: Config -> Config -> Ordering
$ccompare :: Config -> Config -> Ordering
$cp1Ord :: Eq Config
Ord, Int -> Config -> ShowS
[Config] -> ShowS
Config -> FilePath
(Int -> Config -> ShowS)
-> (Config -> FilePath) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Config] -> ShowS
$cshowList :: [Config] -> ShowS
show :: Config -> FilePath
$cshow :: Config -> FilePath
showsPrec :: Int -> Config -> ShowS
$cshowsPrec :: Int -> Config -> ShowS
Show)

-- | Information about source and destination locations of a file\/directory
-- to copy.

data CopyThing = CopyThing FilePath FilePath
  deriving (CopyThing -> CopyThing -> Bool
(CopyThing -> CopyThing -> Bool)
-> (CopyThing -> CopyThing -> Bool) -> Eq CopyThing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyThing -> CopyThing -> Bool
$c/= :: CopyThing -> CopyThing -> Bool
== :: CopyThing -> CopyThing -> Bool
$c== :: CopyThing -> CopyThing -> Bool
Eq, Eq CopyThing
Eq CopyThing
-> (CopyThing -> CopyThing -> Ordering)
-> (CopyThing -> CopyThing -> Bool)
-> (CopyThing -> CopyThing -> Bool)
-> (CopyThing -> CopyThing -> Bool)
-> (CopyThing -> CopyThing -> Bool)
-> (CopyThing -> CopyThing -> CopyThing)
-> (CopyThing -> CopyThing -> CopyThing)
-> Ord CopyThing
CopyThing -> CopyThing -> Bool
CopyThing -> CopyThing -> Ordering
CopyThing -> CopyThing -> CopyThing
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 :: CopyThing -> CopyThing -> CopyThing
$cmin :: CopyThing -> CopyThing -> CopyThing
max :: CopyThing -> CopyThing -> CopyThing
$cmax :: CopyThing -> CopyThing -> CopyThing
>= :: CopyThing -> CopyThing -> Bool
$c>= :: CopyThing -> CopyThing -> Bool
> :: CopyThing -> CopyThing -> Bool
$c> :: CopyThing -> CopyThing -> Bool
<= :: CopyThing -> CopyThing -> Bool
$c<= :: CopyThing -> CopyThing -> Bool
< :: CopyThing -> CopyThing -> Bool
$c< :: CopyThing -> CopyThing -> Bool
compare :: CopyThing -> CopyThing -> Ordering
$ccompare :: CopyThing -> CopyThing -> Ordering
$cp1Ord :: Eq CopyThing
Ord, Int -> CopyThing -> ShowS
[CopyThing] -> ShowS
CopyThing -> FilePath
(Int -> CopyThing -> ShowS)
-> (CopyThing -> FilePath)
-> ([CopyThing] -> ShowS)
-> Show CopyThing
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CopyThing] -> ShowS
$cshowList :: [CopyThing] -> ShowS
show :: CopyThing -> FilePath
$cshow :: CopyThing -> FilePath
showsPrec :: Int -> CopyThing -> ShowS
$cshowsPrec :: Int -> CopyThing -> ShowS
Show)

data Target =
  Target
    { Target -> FilePath
targetHost    :: String
    , Target -> Word
targetPort    :: Word
    , Target -> Shell
targetShell   :: Shell
    , Target -> [FilePath]
targetSshArgs :: [String]
    } deriving (Target -> Target -> Bool
(Target -> Target -> Bool)
-> (Target -> Target -> Bool) -> Eq Target
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c== :: Target -> Target -> Bool
Eq, Eq Target
Eq Target
-> (Target -> Target -> Ordering)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Target)
-> (Target -> Target -> Target)
-> Ord Target
Target -> Target -> Bool
Target -> Target -> Ordering
Target -> Target -> Target
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 :: Target -> Target -> Target
$cmin :: Target -> Target -> Target
max :: Target -> Target -> Target
$cmax :: Target -> Target -> Target
>= :: Target -> Target -> Bool
$c>= :: Target -> Target -> Bool
> :: Target -> Target -> Bool
$c> :: Target -> Target -> Bool
<= :: Target -> Target -> Bool
$c<= :: Target -> Target -> Bool
< :: Target -> Target -> Bool
$c< :: Target -> Target -> Bool
compare :: Target -> Target -> Ordering
$ccompare :: Target -> Target -> Ordering
$cp1Ord :: Eq Target
Ord, Int -> Target -> ShowS
[Target] -> ShowS
Target -> FilePath
(Int -> Target -> ShowS)
-> (Target -> FilePath) -> ([Target] -> ShowS) -> Show Target
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Target] -> ShowS
$cshowList :: [Target] -> ShowS
show :: Target -> FilePath
$cshow :: Target -> FilePath
showsPrec :: Int -> Target -> ShowS
$cshowsPrec :: Int -> Target -> ShowS
Show)

instance FromJSON Config where
  parseJSON :: Value -> Parser Config
parseJSON = FilePath -> (Object -> Parser Config) -> Value -> Parser Config
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"Hapistrano configuration" ((Object -> Parser Config) -> Value -> Parser Config)
-> (Object -> Parser Config) -> Value -> Parser Config
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Path Abs Dir
configDeployPath <- Object
o Object -> Text -> Parser (Path Abs Dir)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"deploy_path"
    let grabPort :: Object -> Parser a
grabPort Object
m = Object
m Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"port" Parser (Maybe a) -> a -> Parser a
forall a. Parser (Maybe a) -> a -> Parser a
.!= a
22
        grabShell :: Object -> Parser Shell
grabShell Object
m = Object
m Object -> Text -> Parser (Maybe Shell)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"shell" Parser (Maybe Shell) -> Shell -> Parser Shell
forall a. Parser (Maybe a) -> a -> Parser a
.!= Shell
Bash
        grabSshArgs :: Object -> Parser [a]
grabSshArgs Object
m = Object
m Object -> Text -> Parser (Maybe [a])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"ssh_args" Parser (Maybe [a]) -> [a] -> Parser [a]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    Maybe FilePath
host             <- Object
o Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"host"
    Word
port             <- Object -> Parser Word
forall a. (FromJSON a, Num a) => Object -> Parser a
grabPort Object
o
    Shell
shell            <- Object -> Parser Shell
grabShell Object
o
    [FilePath]
sshArgs          <- Object -> Parser [FilePath]
forall a. FromJSON a => Object -> Parser [a]
grabSshArgs Object
o
    [Target]
hs               <- (Object
o Object -> Text -> Parser (Maybe [Object])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"targets" Parser (Maybe [Object]) -> [Object] -> Parser [Object]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []) Parser [Object] -> ([Object] -> Parser [Target]) -> Parser [Target]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Object -> Parser Target) -> [Object] -> Parser [Target]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\Object
m ->
      FilePath -> Word -> Shell -> [FilePath] -> Target
Target
        (FilePath -> Word -> Shell -> [FilePath] -> Target)
-> Parser FilePath
-> Parser (Word -> Shell -> [FilePath] -> Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
m Object -> Text -> Parser FilePath
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"host"
        Parser (Word -> Shell -> [FilePath] -> Target)
-> Parser Word -> Parser (Shell -> [FilePath] -> Target)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Parser Word
forall a. (FromJSON a, Num a) => Object -> Parser a
grabPort Object
m
        Parser (Shell -> [FilePath] -> Target)
-> Parser Shell -> Parser ([FilePath] -> Target)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Parser Shell
grabShell Object
m
        Parser ([FilePath] -> Target) -> Parser [FilePath] -> Parser Target
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Parser [FilePath]
forall a. FromJSON a => Object -> Parser [a]
grabSshArgs Object
m)
    let first :: Target -> Maybe FilePath
first Target{FilePath
[FilePath]
Word
Shell
targetSshArgs :: [FilePath]
targetShell :: Shell
targetPort :: Word
targetHost :: FilePath
targetSshArgs :: Target -> [FilePath]
targetShell :: Target -> Shell
targetPort :: Target -> Word
targetHost :: Target -> FilePath
..} = Maybe FilePath
host
        configHosts :: [Target]
configHosts = (Target -> Target -> Bool) -> [Target] -> [Target]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy (Maybe FilePath -> Maybe FilePath -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Maybe FilePath -> Maybe FilePath -> Bool)
-> (Target -> Maybe FilePath) -> Target -> Target -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Target -> Maybe FilePath
first)
          (Maybe Target -> [Target]
forall a. Maybe a -> [a]
maybeToList (FilePath -> Word -> Shell -> [FilePath] -> Target
Target (FilePath -> Word -> Shell -> [FilePath] -> Target)
-> Maybe FilePath -> Maybe (Word -> Shell -> [FilePath] -> Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FilePath
host Maybe (Word -> Shell -> [FilePath] -> Target)
-> Maybe Word -> Maybe (Shell -> [FilePath] -> Target)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word -> Maybe Word
forall (f :: * -> *) a. Applicative f => a -> f a
pure Word
port Maybe (Shell -> [FilePath] -> Target)
-> Maybe Shell -> Maybe ([FilePath] -> Target)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Shell -> Maybe Shell
forall (f :: * -> *) a. Applicative f => a -> f a
pure Shell
shell Maybe ([FilePath] -> Target) -> Maybe [FilePath] -> Maybe Target
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [FilePath] -> Maybe [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FilePath]
sshArgs) [Target] -> [Target] -> [Target]
forall a. [a] -> [a] -> [a]
++ [Target]
hs)
        source :: Object -> Parser Source
source Object
m =
              FilePath -> FilePath -> Source
GitRepository (FilePath -> FilePath -> Source)
-> Parser FilePath -> Parser (FilePath -> Source)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
m Object -> Text -> Parser FilePath
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"repo" Parser (FilePath -> Source) -> Parser FilePath -> Parser Source
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
m Object -> Text -> Parser FilePath
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"revision"
          Parser Source -> Parser Source -> Parser Source
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Path Abs Dir -> Source
LocalDirectory (Path Abs Dir -> Source) -> Parser (Path Abs Dir) -> Parser Source
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
m Object -> Text -> Parser (Path Abs Dir)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"local_directory"
    Source
configSource  <- Object -> Parser Source
source Object
o
    Maybe GenericCommand
configRestartCommand <- (Object
o Object -> Text -> Parser (Maybe FilePath)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"restart_command") Parser (Maybe FilePath)
-> (Maybe FilePath -> Parser (Maybe GenericCommand))
-> Parser (Maybe GenericCommand)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      Parser (Maybe GenericCommand)
-> (FilePath -> Parser (Maybe GenericCommand))
-> Maybe FilePath
-> Parser (Maybe GenericCommand)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe GenericCommand -> Parser (Maybe GenericCommand)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GenericCommand
forall a. Maybe a
Nothing) ((GenericCommand -> Maybe GenericCommand)
-> Parser GenericCommand -> Parser (Maybe GenericCommand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GenericCommand -> Maybe GenericCommand
forall a. a -> Maybe a
Just (Parser GenericCommand -> Parser (Maybe GenericCommand))
-> (FilePath -> Parser GenericCommand)
-> FilePath
-> Parser (Maybe GenericCommand)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Parser GenericCommand
mkCmd)
    Maybe [GenericCommand]
configBuildScript <- Object
o Object -> Text -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"build_script" Parser (Maybe [FilePath])
-> (Maybe [FilePath] -> Parser (Maybe [GenericCommand]))
-> Parser (Maybe [GenericCommand])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      Parser (Maybe [GenericCommand])
-> ([FilePath] -> Parser (Maybe [GenericCommand]))
-> Maybe [FilePath]
-> Parser (Maybe [GenericCommand])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe [GenericCommand] -> Parser (Maybe [GenericCommand])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [GenericCommand]
forall a. Maybe a
Nothing) (([GenericCommand] -> Maybe [GenericCommand])
-> Parser [GenericCommand] -> Parser (Maybe [GenericCommand])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [GenericCommand] -> Maybe [GenericCommand]
forall a. a -> Maybe a
Just (Parser [GenericCommand] -> Parser (Maybe [GenericCommand]))
-> ([FilePath] -> Parser [GenericCommand])
-> [FilePath]
-> Parser (Maybe [GenericCommand])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Parser GenericCommand)
-> [FilePath] -> Parser [GenericCommand]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> Parser GenericCommand
mkCmd)
    [CopyThing]
configCopyFiles  <- Object
o Object -> Text -> Parser (Maybe [CopyThing])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"copy_files" Parser (Maybe [CopyThing]) -> [CopyThing] -> Parser [CopyThing]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [CopyThing]
configCopyDirs   <- Object
o Object -> Text -> Parser (Maybe [CopyThing])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"copy_dirs"  Parser (Maybe [CopyThing]) -> [CopyThing] -> Parser [CopyThing]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [FilePath]
configLinkedFiles <- Object
o Object -> Text -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"linked_files" Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [FilePath]
configLinkedDirs  <- Object
o Object -> Text -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"linked_dirs"  Parser (Maybe [FilePath]) -> [FilePath] -> Parser [FilePath]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    Bool
configVcAction    <- Object
o Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"vc_action" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
True
    Maybe [GenericCommand]
configRunLocally  <- Object
o Object -> Text -> Parser (Maybe [FilePath])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"run_locally" Parser (Maybe [FilePath])
-> (Maybe [FilePath] -> Parser (Maybe [GenericCommand]))
-> Parser (Maybe [GenericCommand])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      Parser (Maybe [GenericCommand])
-> ([FilePath] -> Parser (Maybe [GenericCommand]))
-> Maybe [FilePath]
-> Parser (Maybe [GenericCommand])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe [GenericCommand] -> Parser (Maybe [GenericCommand])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [GenericCommand]
forall a. Maybe a
Nothing) (([GenericCommand] -> Maybe [GenericCommand])
-> Parser [GenericCommand] -> Parser (Maybe [GenericCommand])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [GenericCommand] -> Maybe [GenericCommand]
forall a. a -> Maybe a
Just (Parser [GenericCommand] -> Parser (Maybe [GenericCommand]))
-> ([FilePath] -> Parser [GenericCommand])
-> [FilePath]
-> Parser (Maybe [GenericCommand])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Parser GenericCommand)
-> [FilePath] -> Parser [GenericCommand]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> Parser GenericCommand
mkCmd)
    TargetSystem
configTargetSystem <- Object
o Object -> Text -> Parser (Maybe TargetSystem)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"linux" Parser (Maybe TargetSystem) -> TargetSystem -> Parser TargetSystem
forall a. Parser (Maybe a) -> a -> Parser a
.!= TargetSystem
GNULinux
    Maybe ReleaseFormat
configReleaseFormat <- Object
o Object -> Text -> Parser (Maybe ReleaseFormat)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"release_format"
    Maybe Natural
configKeepReleases <- Object
o Object -> Text -> Parser (Maybe Natural)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"keep_releases"
    Maybe (Path Rel Dir)
configWorkingDir <- Object
o Object -> Text -> Parser (Maybe (Path Rel Dir))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"working_directory"
    Config -> Parser Config
forall (m :: * -> *) a. Monad m => a -> m a
return Config :: Path Abs Dir
-> [Target]
-> Source
-> Maybe GenericCommand
-> Maybe [GenericCommand]
-> [CopyThing]
-> [CopyThing]
-> [FilePath]
-> [FilePath]
-> Bool
-> Maybe [GenericCommand]
-> TargetSystem
-> Maybe ReleaseFormat
-> Maybe Natural
-> Maybe (Path Rel Dir)
-> Config
Config {Bool
[FilePath]
[Target]
[CopyThing]
Maybe Natural
Maybe [GenericCommand]
Maybe (Path Rel Dir)
Maybe ReleaseFormat
Maybe GenericCommand
Path Abs Dir
TargetSystem
Source
configWorkingDir :: Maybe (Path Rel Dir)
configKeepReleases :: Maybe Natural
configReleaseFormat :: Maybe ReleaseFormat
configTargetSystem :: TargetSystem
configRunLocally :: Maybe [GenericCommand]
configVcAction :: Bool
configLinkedDirs :: [FilePath]
configLinkedFiles :: [FilePath]
configCopyDirs :: [CopyThing]
configCopyFiles :: [CopyThing]
configBuildScript :: Maybe [GenericCommand]
configRestartCommand :: Maybe GenericCommand
configSource :: Source
configHosts :: [Target]
configDeployPath :: Path Abs Dir
configWorkingDir :: Maybe (Path Rel Dir)
configKeepReleases :: Maybe Natural
configReleaseFormat :: Maybe ReleaseFormat
configTargetSystem :: TargetSystem
configRunLocally :: Maybe [GenericCommand]
configVcAction :: Bool
configLinkedDirs :: [FilePath]
configLinkedFiles :: [FilePath]
configCopyDirs :: [CopyThing]
configCopyFiles :: [CopyThing]
configBuildScript :: Maybe [GenericCommand]
configRestartCommand :: Maybe GenericCommand
configSource :: Source
configHosts :: [Target]
configDeployPath :: Path Abs Dir
..}

instance FromJSON CopyThing where
  parseJSON :: Value -> Parser CopyThing
parseJSON = FilePath
-> (Object -> Parser CopyThing) -> Value -> Parser CopyThing
forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
withObject FilePath
"src and dest of a thing to copy" ((Object -> Parser CopyThing) -> Value -> Parser CopyThing)
-> (Object -> Parser CopyThing) -> Value -> Parser CopyThing
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    FilePath -> FilePath -> CopyThing
CopyThing (FilePath -> FilePath -> CopyThing)
-> Parser FilePath -> Parser (FilePath -> CopyThing)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Text -> Parser FilePath
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"src") Parser (FilePath -> CopyThing)
-> Parser FilePath -> Parser CopyThing
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Text -> Parser FilePath
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"dest")

instance FromJSON TargetSystem where
  parseJSON :: Value -> Parser TargetSystem
parseJSON = FilePath
-> (Bool -> Parser TargetSystem) -> Value -> Parser TargetSystem
forall a. FilePath -> (Bool -> Parser a) -> Value -> Parser a
withBool FilePath
"linux" ((Bool -> Parser TargetSystem) -> Value -> Parser TargetSystem)
-> (Bool -> Parser TargetSystem) -> Value -> Parser TargetSystem
forall a b. (a -> b) -> a -> b
$
    TargetSystem -> Parser TargetSystem
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TargetSystem -> Parser TargetSystem)
-> (Bool -> TargetSystem) -> Bool -> Parser TargetSystem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
      Bool
True  -> TargetSystem
GNULinux
      Bool
False -> TargetSystem
BSD

mkCmd :: String -> Parser GenericCommand
mkCmd :: FilePath -> Parser GenericCommand
mkCmd FilePath
raw =
  case FilePath -> Maybe GenericCommand
mkGenericCommand FilePath
raw of
    Maybe GenericCommand
Nothing  -> FilePath -> Parser GenericCommand
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"invalid restart command"
    Just GenericCommand
cmd -> GenericCommand -> Parser GenericCommand
forall (m :: * -> *) a. Monad m => a -> m a
return GenericCommand
cmd