{-# LANGUAGE CPP #-} module HaskellCI.Bash.Template ( -- * Input Z (..), defaultZ, -- * Rendering renderIO, render, ) where import HaskellCI.Prelude import Control.Monad (forM_) import qualified Zinza data Z = Z { zJobs :: [String] , zRegendata :: String , zBlocks :: [String] , zTestsCond :: String , zBenchCond :: String , zApt :: [String] , zNotNull :: [String] -> Bool , zUnwords :: [String] -> String } deriving (Generic) defaultZ :: Z defaultZ = Z { zJobs = [] , zRegendata = "[]" , zBlocks = [] , zTestsCond = "1" , zBenchCond = "1" , zApt = [] , zNotNull = not . null , zUnwords = unwords } instance Zinza.Zinza Z where toType = Zinza.genericToTypeSFP toValue = Zinza.genericToValueSFP fromValue = Zinza.genericFromValueSFP ------------------------------------------------------------------------------- -- Development ------------------------------------------------------------------------------- -- #define DEVELOPMENT 1 #ifdef DEVELOPMENT renderIO :: Z -> IO String renderIO z = do template <- Zinza.parseAndCompileTemplateIO "haskell-ci.sh.zinza" template z #endif ------------------------------------------------------------------------------- -- Production ------------------------------------------------------------------------------- #ifndef DEVELOPMENT renderIO :: Z -> IO String renderIO = return . render #endif type Writer a = (String, a) tell :: String -> Writer (); tell x = (x, ()) execWriter :: Writer a -> String; execWriter = fst -- To generate: -- -- :m *HaskellCI.Bash.Template -- Zinza.parseAndCompileModuleIO (Zinza.simpleConfig "Module" [] :: Zinza.ModuleConfig Z) "haskell-ci.sh.zinza" >>= putStr render :: Z -> String render z_root = execWriter $ do tell "#!/bin/bash\n" tell "# shellcheck disable=SC2086,SC2016,SC2046\n" tell "# REGENDATA " tell (zRegendata z_root) tell "\n" tell "\n" tell "set -o pipefail\n" tell "\n" tell "# Mode\n" tell "##############################################################################\n" tell "\n" tell "if [ \"$1\" = \"indocker\" ]; then\n" tell " INDOCKER=true\n" tell " shift\n" tell "else\n" tell " INDOCKER=false\n" tell "fi\n" tell "\n" tell "# Run configuration\n" tell "##############################################################################\n" tell "\n" tell "CFG_CABAL_STORE_CACHE=\"\"\n" tell "CFG_CABAL_REPO_CACHE=\"\"\n" tell "CFG_JOBS=\"" tell (zUnwords z_root (zJobs z_root)) tell "\"\n" tell "CFG_CABAL_UPDATE=false\n" tell "\n" tell "SCRIPT_NAME=$(basename \"$0\")\n" tell "START_TIME=\"$(date +'%s')\"\n" tell "\n" tell "XDG_CONFIG_HOME=${XDG_CONFIG_HOME:-$HOME/.config}\n" tell "\n" tell "# Job configuration\n" tell "##############################################################################\n" tell "\n" tell "GHC_VERSION=\"non-existing\"\n" tell "CABAL_VERSION=3.2\n" tell "HEADHACKAGE=false\n" tell "\n" tell "# Locale\n" tell "##############################################################################\n" tell "\n" tell "export LC_ALL=C.UTF-8\n" tell "\n" tell "# Utilities\n" tell "##############################################################################\n" tell "\n" tell "SGR_RED='\\033[1;31m'\n" tell "SGR_GREEN='\\033[1;32m'\n" tell "SGR_BLUE='\\033[1;34m'\n" tell "SGR_CYAN='\\033[1;96m'\n" tell "SGR_RESET='\\033[0m' # No Color\n" tell "\n" tell "put_info() {\n" tell " printf \"$SGR_CYAN%s$SGR_RESET\\n\" \"### $*\"\n" tell "}\n" tell "\n" tell "put_error() {\n" tell " printf \"$SGR_RED%s$SGR_RESET\\n\" \"!!! $*\"\n" tell "}\n" tell "\n" tell "run_cmd() {\n" tell " local PRETTYCMD=\"$*\"\n" tell " local PROMPT\n" tell " if $INDOCKER; then\n" tell " PROMPT=\"$(pwd) >>>\"\n" tell " else\n" tell " PROMPT=\">>>\"\n" tell " fi\n" tell "\n" tell " printf \"$SGR_BLUE%s %s$SGR_RESET\\n\" \"$PROMPT\" \"$PRETTYCMD\"\n" tell "\n" tell " local start_time end_time cmd_duration total_duration\n" tell " start_time=$(date +'%s')\n" tell "\n" tell " \"$@\"\n" tell " local RET=$?\n" tell "\n" tell " end_time=$(date +'%s')\n" tell " cmd_duration=$((end_time - start_time))\n" tell " total_duration=$((end_time - START_TIME))\n" tell "\n" tell " cmd_min=$((cmd_duration / 60))\n" tell " cmd_sec=$((cmd_duration % 60))\n" tell "\n" tell " total_min=$((total_duration / 60))\n" tell " total_sec=$((total_duration % 60))\n" tell "\n" tell " if [ $RET -eq 0 ]; then\n" tell " printf \"$SGR_GREEN%s$SGR_RESET (%dm%02ds; %dm%02ds)\\n\" \"<<< $PRETTYCMD\" \"$cmd_min\" \"$cmd_sec\" \"$total_min\" \"$total_sec\"\n" tell " else\n" tell " printf \"$SGR_RED%s$SGR_RESET\\n\" \"!!! $PRETTYCMD\"\n" tell " exit 1\n" tell " fi\n" tell "}\n" tell "\n" tell "run_cmd_if() {\n" tell " local COND=$1\n" tell " shift\n" tell "\n" tell " if [ $COND -eq 1 ]; then\n" tell " run_cmd \"$@\"\n" tell " else\n" tell " local PRETTYCMD=\"$*\"\n" tell " local PROMPT\n" tell " PROMPT=\"$(pwd) (skipping) >>>\"\n" tell "\n" tell " printf \"$SGR_BLUE%s %s$SGR_RESET\\n\" \"$PROMPT\" \"$PRETTYCMD\"\n" tell " fi\n" tell "}\n" tell "\n" tell "run_cmd_unchecked() {\n" tell " local PRETTYCMD=\"$*\"\n" tell " local PROMPT\n" tell " if $INDOCKER; then\n" tell " PROMPT=\"$(pwd) >>>\"\n" tell " else\n" tell " PROMPT=\">>>\"\n" tell " fi\n" tell "\n" tell " printf \"$SGR_BLUE%s %s$SGR_RESET\\n\" \"$PROMPT\" \"$PRETTYCMD\"\n" tell "\n" tell " local start_time end_time cmd_duration total_duration cmd_min cmd_sec total_min total_sec\n" tell " start_time=$(date +'%s')\n" tell "\n" tell " \"$@\"\n" tell "\n" tell " end_time=$(date +'%s')\n" tell " cmd_duration=$((end_time - start_time))\n" tell " total_duration=$((end_time - START_TIME))\n" tell "\n" tell " cmd_min=$((cmd_duration / 60))\n" tell " cmd_sec=$((cmd_duration % 60))\n" tell "\n" tell " total_min=$((total_duration / 60))\n" tell " total_sec=$((total_duration % 60))\n" tell "\n" tell " printf \"$SGR_GREEN%s$SGR_RESET (%dm%02ds; %dm%02ds)\\n\" \"<<< $PRETTYCMD\" \"$cmd_min\" \"$cmd_sec\" \"$total_min\" \"$total_sec\"\n" tell "}\n" tell "\n" tell "change_dir() {\n" tell " local DIR=$1\n" tell " if [ -d \"$DIR\" ]; then\n" tell " printf \"$SGR_BLUE%s$SGR_RESET\\n\" \"change directory to $DIR\"\n" tell " cd \"$DIR\" || exit 1\n" tell " else\n" tell " printf \"$SGR_RED%s$SGR_RESET\\n\" \"!!! cd $DIR\"\n" tell " exit 1\n" tell " fi\n" tell "}\n" tell "\n" tell "change_dir_if() {\n" tell " local COND=$1\n" tell " local DIR=$2\n" tell "\n" tell " if [ $COND -ne 0 ]; then\n" tell " change_dir \"$DIR\"\n" tell " fi\n" tell "}\n" tell "\n" tell "echo_to() {\n" tell " local DEST=$1\n" tell " local CONTENTS=$2\n" tell "\n" tell " echo \"$CONTENTS\" >> \"$DEST\"\n" tell "}\n" tell "\n" tell "echo_if_to() {\n" tell " local COND=$1\n" tell " local DEST=$2\n" tell " local CONTENTS=$3\n" tell "\n" tell " if [ $COND -ne 0 ]; then\n" tell " echo_to \"$DEST\" \"$CONTENTS\"\n" tell " fi\n" tell "}\n" tell "\n" tell "install_cabalplan() {\n" tell " put_info \"installing cabal-plan\"\n" tell "\n" tell " if [ ! -e $CABAL_REPOCACHE/downloads/cabal-plan ]; then\n" tell " curl -L https://github.com/haskell-hvr/cabal-plan/releases/download/v0.6.2.0/cabal-plan-0.6.2.0-x86_64-linux.xz > /tmp/cabal-plan.xz || exit 1\n" tell " (cd /tmp && echo \"de73600b1836d3f55e32d80385acc055fd97f60eaa0ab68a755302685f5d81bc cabal-plan.xz\" | sha256sum -c -)|| exit 1\n" tell " mkdir -p $CABAL_REPOCACHE/downloads\n" tell " xz -d < /tmp/cabal-plan.xz > $CABAL_REPOCACHE/downloads/cabal-plan || exit 1\n" tell " chmod a+x $CABAL_REPOCACHE/downloads/cabal-plan || exit 1\n" tell " fi\n" tell "\n" tell " mkdir -p $CABAL_DIR/bin || exit 1\n" tell " ln -s $CABAL_REPOCACHE/downloads/cabal-plan $CABAL_DIR/bin/cabal-plan || exit 1\n" tell "}\n" tell "\n" tell "# Help\n" tell "##############################################################################\n" tell "\n" tell "show_usage() {\n" tell "cat < $BUILDDIR/cabal/config < do tell z_var0_block tell "\n" tell "\n" tell "# Done\n" tell "run_cmd echo OK\n"