{-# LANGUAGE TemplateHaskell #-}

module System.Hapistrano.Maintenance
  ( writeMaintenanceFile
  , deleteMaintenanceFile
  ) where

import Path (Abs, Dir, File, Path, Rel, (</>))
import System.Hapistrano.Commands
import System.Hapistrano.Core
import System.Hapistrano.Types

-- | It writes an HTML page in the given directory with a given name
writeMaintenanceFile ::
     Path Abs Dir -> Path Rel Dir -> Path Rel File -> Hapistrano ()
writeMaintenanceFile :: Path Abs Dir -> Path Rel Dir -> Path Rel File -> Hapistrano ()
writeMaintenanceFile Path Abs Dir
deployPath Path Rel Dir
relDir Path Rel File
fileName =
  let foo :: Path Abs Dir
foo = Path Abs Dir
deployPath forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel Dir
relDir
      fullpath :: Path Rel File
fullpath = Path Rel Dir
relDir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
fileName
      root :: Path Abs File
root = Path Abs Dir
deployPath forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
fullpath
   in do forall a. Command a => a -> Maybe Release -> Hapistrano (Result a)
exec (Path Abs Dir -> MkDir
MkDir Path Abs Dir
foo) forall a. Maybe a
Nothing
         forall a. Command a => a -> Maybe Release -> Hapistrano (Result a)
exec (Path Abs File -> Touch
Touch Path Abs File
root) forall a. Maybe a
Nothing
         forall a. Command a => a -> Maybe Release -> Hapistrano (Result a)
exec (Path Abs File -> String -> BasicWrite
BasicWrite Path Abs File
root String
maintenancePageContent) forall a. Maybe a
Nothing

-- | It deletes the file in the given directory with the given name
deleteMaintenanceFile ::
     Path Abs Dir -> Path Rel Dir -> Path Rel File -> Hapistrano ()
deleteMaintenanceFile :: Path Abs Dir -> Path Rel Dir -> Path Rel File -> Hapistrano ()
deleteMaintenanceFile Path Abs Dir
deployPath Path Rel Dir
relDir Path Rel File
fileName =
  let fullpath :: Path Rel File
fullpath = Path Rel Dir
relDir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
fileName
      root :: Path Abs File
root = Path Abs Dir
deployPath forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel File
fullpath
   in forall a. Command a => a -> Maybe Release -> Hapistrano (Result a)
exec (forall t. Path Abs t -> Rm
Rm Path Abs File
root) forall a. Maybe a
Nothing

maintenancePageContent :: String
maintenancePageContent :: String
maintenancePageContent =
  String
"<!DOCTYPE html> \n\
  \<html>\n\
  \ <head>\n\
  \ <title>Maintenance</title>\n\
  \ <style type=\"text/css\">\n\
  \   body {\n\
  \     width: 400px;\n\
  \     margin: 100px auto;\n\
  \     font: 300 120% \"OpenSans\", \"Helvetica Neue\", \"Helvetica\", Arial, Verdana, sans-serif;\n\
  \    }\n\
  \   h1 {\n\
  \     font-weight: 300;\n\
  \    }\n\
  \ </style>\n\
  \ </head>\n\
  \ <body>\n\
  \   <h1>Maintenance</h1>\n\
  \   <p>The system is down for maintenance</p>\n\
  \   <p>It'll be back shortly</p>\n\
  \ </body>\n\
  \</html>"