-- |
-- Module      :  System.Config
-- Copyright   :  © 2015-Present Stack Builders
-- License     :  MIT
--
-- Stability   :  experimental
-- Portability :  portable
--
-- Definitions for types and functions related to the configuration
-- of the Hapistrano tool.
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE TemplateHaskell   #-}

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

module System.Hapistrano.Config
  ( Config (..)
  , CopyThing (..)
  , Target (..)
  , deployStateFilename)
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    (ReleaseFormat (..), Shell (..),
                                             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 -> Bool
configKeepOneFailed        :: !Bool
  -- ^ Specifies whether to keep all failed releases along with the successful releases
  -- or just the latest failed (at least this one should be kept for debugging purposes).
  -- The @--keep-one-failed@ argument passed via the CLI takes precedence over this value.
  -- If neither CLI or configuration file value is specified, it defaults to `False`
  -- (i.e. keep all failed releases).
  , Config -> Maybe (Path Rel Dir)
configWorkingDir           :: !(Maybe (Path Rel Dir))
  , Config -> Path Rel Dir
configMaintenanceDirectory :: !(Path Rel Dir)
  , Config -> Path Rel File
configMaintenanceFileName  :: !(Path Rel File)
  } deriving (Config -> Config -> Bool
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
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
Ord, Int -> Config -> ShowS
[Config] -> ShowS
Config -> FilePath
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
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
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
Ord, Int -> CopyThing -> ShowS
[CopyThing] -> ShowS
CopyThing -> FilePath
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)

-- | Datatype that holds information about the target host.

data Target =
  Target
    { Target -> FilePath
targetHost    :: String
    , Target -> Word
targetPort    :: Word
    , Target -> Shell
targetShell   :: Shell
    , Target -> [FilePath]
targetSshArgs :: [String]
    } deriving (Target -> Target -> Bool
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
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
Ord, Int -> Target -> ShowS
[Target] -> ShowS
Target -> FilePath
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 = forall a.
FilePath -> (KeyMap Value -> Parser a) -> Value -> Parser a
withObject FilePath
"Hapistrano configuration" forall a b. (a -> b) -> a -> b
$ \KeyMap Value
o -> do
    Path Abs Dir
configDeployPath <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"deploy_path"
    let grabPort :: KeyMap Value -> Parser a
grabPort KeyMap Value
m = KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"port" forall a. Parser (Maybe a) -> a -> Parser a
.!= a
22
        grabShell :: KeyMap Value -> Parser Shell
grabShell KeyMap Value
m = KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"shell" forall a. Parser (Maybe a) -> a -> Parser a
.!= Shell
Bash
        grabSshArgs :: KeyMap Value -> Parser [a]
grabSshArgs KeyMap Value
m = KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"ssh_args" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    Maybe FilePath
host             <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"host"
    Word
port             <- forall {a}. (FromJSON a, Num a) => KeyMap Value -> Parser a
grabPort KeyMap Value
o
    Shell
shell            <- KeyMap Value -> Parser Shell
grabShell KeyMap Value
o
    [FilePath]
sshArgs          <- forall {a}. FromJSON a => KeyMap Value -> Parser [a]
grabSshArgs KeyMap Value
o
    [Target]
hs               <- (KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"targets" forall a. Parser (Maybe a) -> a -> Parser a
.!= []) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\KeyMap Value
m ->
      FilePath -> Word -> Shell -> [FilePath] -> Target
Target
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"host"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall {a}. (FromJSON a, Num a) => KeyMap Value -> Parser a
grabPort KeyMap Value
m
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> KeyMap Value -> Parser Shell
grabShell KeyMap Value
m
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall {a}. FromJSON a => KeyMap Value -> Parser [a]
grabSshArgs KeyMap Value
m)
    let configHosts :: [Target]
configHosts = forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Target -> FilePath
targetHost)
          (forall a. Maybe a -> [a]
maybeToList (FilePath -> Word -> Shell -> [FilePath] -> Target
Target forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FilePath
host forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Word
port forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Shell
shell forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [FilePath]
sshArgs) forall a. [a] -> [a] -> [a]
++ [Target]
hs)
        source :: KeyMap Value -> Parser Source
source KeyMap Value
m =
              FilePath -> FilePath -> Source
GitRepository forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"repo" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"revision"
          forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Path Abs Dir -> Source
LocalDirectory forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> KeyMap Value
m forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"local_directory"
    Source
configSource  <- KeyMap Value -> Parser Source
source KeyMap Value
o
    Maybe GenericCommand
configRestartCommand <- (KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"restart_command") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Parser GenericCommand
mkCmd)
    Maybe [GenericCommand]
configBuildScript <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"build_script" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> Parser GenericCommand
mkCmd)
    [CopyThing]
configCopyFiles  <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"copy_files" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [CopyThing]
configCopyDirs   <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"copy_dirs"  forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [FilePath]
configLinkedFiles <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"linked_files" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    [FilePath]
configLinkedDirs  <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"linked_dirs"  forall a. Parser (Maybe a) -> a -> Parser a
.!= []
    Bool
configVcAction    <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"vc_action" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
True
    Maybe [GenericCommand]
configRunLocally  <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"run_locally" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FilePath -> Parser GenericCommand
mkCmd)
    TargetSystem
configTargetSystem <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"linux" forall a. Parser (Maybe a) -> a -> Parser a
.!= TargetSystem
GNULinux
    Maybe ReleaseFormat
configReleaseFormat <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"release_format"
    Maybe Natural
configKeepReleases <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"keep_releases"
    Bool
configKeepOneFailed <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"keep_one_failed" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
    Maybe (Path Rel Dir)
configWorkingDir <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"working_directory"
    Path Rel Dir
configMaintenanceDirectory <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"maintenance_directory" forall a. Parser (Maybe a) -> a -> Parser a
.!= $(mkRelDir "maintenance")
    Path Rel File
configMaintenanceFileName <- KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser (Maybe a)
.:? Key
"maintenance_filename" forall a. Parser (Maybe a) -> a -> Parser a
.!= $(mkRelFile "maintenance.html")
    forall (m :: * -> *) a. Monad m => a -> m a
return Config {Bool
[FilePath]
[Target]
[CopyThing]
Maybe Natural
Maybe [GenericCommand]
Maybe (Path Rel Dir)
Maybe ReleaseFormat
Maybe GenericCommand
Path Abs Dir
Path Rel File
Path Rel Dir
TargetSystem
Source
configMaintenanceFileName :: Path Rel File
configMaintenanceDirectory :: Path Rel Dir
configWorkingDir :: Maybe (Path Rel Dir)
configKeepOneFailed :: Bool
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
configMaintenanceFileName :: Path Rel File
configMaintenanceDirectory :: Path Rel Dir
configWorkingDir :: Maybe (Path Rel Dir)
configKeepOneFailed :: Bool
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 = forall a.
FilePath -> (KeyMap Value -> Parser a) -> Value -> Parser a
withObject FilePath
"src and dest of a thing to copy" forall a b. (a -> b) -> a -> b
$ \KeyMap Value
o ->
    FilePath -> FilePath -> CopyThing
CopyThing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"src") forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (KeyMap Value
o forall a. FromJSON a => KeyMap Value -> Key -> Parser a
.: Key
"dest")

instance FromJSON TargetSystem where
  parseJSON :: Value -> Parser TargetSystem
parseJSON = forall a. FilePath -> (Bool -> Parser a) -> Value -> Parser a
withBool FilePath
"linux" forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a. Applicative f => a -> f a
pure 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  -> forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"invalid restart command"
    Just GenericCommand
cmd -> forall (m :: * -> *) a. Monad m => a -> m a
return GenericCommand
cmd

-- | Constant with the name of the file used to store
-- the deployment state information.

deployStateFilename :: String
deployStateFilename :: FilePath
deployStateFilename = FilePath
".hapistrano_deploy_state"