diff -pruN 1.32.0-1/benchmark/deep-nested-large-record/Main.hs 1.40.2-1/benchmark/deep-nested-large-record/Main.hs
--- 1.32.0-1/benchmark/deep-nested-large-record/Main.hs	2020-05-08 15:20:22.000000000 +0000
+++ 1.40.2-1/benchmark/deep-nested-large-record/Main.hs	2001-09-09 01:46:40.000000000 +0000
@@ -1,11 +1,12 @@
 {-# LANGUAGE OverloadedStrings #-}
 module Main (main) where
 
-import Gauge(defaultMain)
+import Data.Void (Void)
+import Gauge     (defaultMain)
 
-import qualified Data.Sequence as Seq
-import qualified Dhall.Core as Core
-import qualified Dhall.Import as Import
+import qualified Data.Sequence   as Seq
+import qualified Dhall.Core      as Core
+import qualified Dhall.Import    as Import
 import qualified Dhall.TypeCheck as TypeCheck
 import qualified Gauge
 
@@ -21,16 +22,19 @@ dhallPreludeImport = Core.Import
     }
   }
 
-issue412 :: Core.Expr s TypeCheck.X -> Gauge.Benchmarkable
+issue412 :: Core.Expr s Void -> Gauge.Benchmarkable
 issue412 prelude = Gauge.whnf TypeCheck.typeOf expr
   where
     expr
       = Core.Let (Core.Binding Nothing "prelude" Nothing Nothing Nothing prelude)
       $ Core.ListLit Nothing
       $ Seq.replicate 5
-      $ Core.Var (Core.V "prelude" 0) `Core.Field` "types" `Core.Field` "Little" `Core.Field` "Foo"
+      $ Core.Var (Core.V "prelude" 0) `Core.Field` types `Core.Field` little `Core.Field` foo
+    types = Core.makeFieldSelection "types"
+    little = Core.makeFieldSelection "little"
+    foo = Core.makeFieldSelection "Foo"
 
-unionPerformance :: Core.Expr s TypeCheck.X -> Gauge.Benchmarkable
+unionPerformance :: Core.Expr s Void -> Gauge.Benchmarkable
 unionPerformance prelude = Gauge.whnf TypeCheck.typeOf expr
   where
     expr =
@@ -48,17 +52,22 @@ unionPerformance prelude = Gauge.whnf Ty
                         Nothing
                         Nothing
                         Nothing
-                        (prelude `Core.Field` "types" `Core.Field` "Big")
+                        (prelude `Core.Field` types `Core.Field` big)
                     )
-                    (Core.Prefer Core.PreferFromSource "big" "big")
+                    (Core.Prefer mempty Core.PreferFromSource "big" "big")
                 )
             )
             "x"
+    types = Core.makeFieldSelection "types"
+    big = Core.makeFieldSelection "Big"
 
 main :: IO ()
-main = do
-  prelude <- Import.load (Core.Embed dhallPreludeImport)
+main =
   defaultMain
-    [ Gauge.bench "issue 412" (issue412 prelude)
-    , Gauge.bench "union performance" (unionPerformance prelude)
+    [ Gauge.env prelude $ \p ->
+      Gauge.bgroup "Prelude"
+        [ Gauge.bench "issue 412" (issue412 p)
+        , Gauge.bench "union performance" (unionPerformance p)
+        ]
     ]
+  where prelude = Import.load (Core.Embed dhallPreludeImport)
diff -pruN 1.32.0-1/benchmark/examples/cpkg.dhall 1.40.2-1/benchmark/examples/cpkg.dhall
--- 1.32.0-1/benchmark/examples/cpkg.dhall	1970-01-01 00:00:00.000000000 +0000
+++ 1.40.2-1/benchmark/examples/cpkg.dhall	2001-09-09 01:46:40.000000000 +0000
@@ -0,0 +1,49991 @@
+-- Generated from https://github.com/vmchale/cpkg/blob/master/pkgs/pkg-set.dhall by running dhall resolve
+
+let concatMapSep =
+      λ(_ : Text) →
+      λ(_ : Type) →
+      λ(_ : _ → Text) →
+      λ(_ : List _@1) →
+        merge
+          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+          ( List/fold
+              _@2
+              _
+              < Empty | NonEmpty : Text >
+              ( λ(_ : _@2) →
+                λ(_ : < Empty | NonEmpty : Text >) →
+                  merge
+                    { Empty = < Empty | NonEmpty : Text >.NonEmpty (_@3 _@1)
+                    , NonEmpty =
+                        λ(_ : Text) →
+                          < Empty | NonEmpty : Text >.NonEmpty
+                            "${_@4 _@2}${_@6}${_}"
+                    }
+                    _
+              )
+              < Empty | NonEmpty : Text >.Empty
+          )
+
+let concat =
+      λ(_ : List Text) →
+        List/fold Text _ Text (λ(_ : Text) → λ(_ : Text) → "${_@1}${_}") ""
+
+let types =
+      { ABI = < GNU | GNUabi64 | GNUeabi | GNUeabihf | GNUspe | MinGw >
+      , Arch =
+          < AArch
+          | Alpha
+          | Arm
+          | HPPA
+          | HPPA64
+          | M68k
+          | Mips
+          | Mips64
+          | Mips64El
+          | MipsEl
+          | MipsIsa32r6
+          | MipsIsa32r6El
+          | MipsIsa64r6
+          | MipsIsa64r6El
+          | PowerPC
+          | PowerPC64
+          | PowerPC64le
+          | RISCV64
+          | S390x
+          | SH4
+          | Sparc64
+          | X64
+          | X86
+          >
+      , BuildVars =
+          { binDirs : List Text
+          , buildArch :
+              < AArch
+              | Alpha
+              | Arm
+              | HPPA
+              | HPPA64
+              | M68k
+              | Mips
+              | Mips64
+              | Mips64El
+              | MipsEl
+              | MipsIsa32r6
+              | MipsIsa32r6El
+              | MipsIsa64r6
+              | MipsIsa64r6El
+              | PowerPC
+              | PowerPC64
+              | PowerPC64le
+              | RISCV64
+              | S390x
+              | SH4
+              | Sparc64
+              | X64
+              | X86
+              >
+          , buildOS :
+              < AIX
+              | Android
+              | Darwin
+              | Dragonfly
+              | FreeBSD
+              | Haiku
+              | Hurd
+              | IOS
+              | Linux
+              | NetBSD
+              | NoOs
+              | OpenBSD
+              | Redox
+              | Solaris
+              | Windows
+              >
+          , cpus : Natural
+          , currentDir : Text
+          , includeDirs : List Text
+          , installDir : Text
+          , isCross : Bool
+          , linkDirs : List Text
+          , preloadLibs : List Text
+          , shareDirs : List Text
+          , static : Bool
+          , targetTriple :
+              Optional
+                { abi :
+                    Optional
+                      < GNU | GNUabi64 | GNUeabi | GNUeabihf | GNUspe | MinGw >
+                , arch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                , os :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                }
+          }
+      , Command =
+          < Call :
+              { arguments : List Text
+              , environment : Optional (List { value : Text, var : Text })
+              , procDir : Optional Text
+              , program : Text
+              }
+          | CopyFile : { dest : Text, src : Text }
+          | CreateDirectory : { dir : Text }
+          | MakeExecutable : { file : Text }
+          | Patch : { patchContents : Text }
+          | Symlink : { linkName : Text, tgt : Text }
+          | SymlinkBinary : { file : Text }
+          | SymlinkManpage : { file : Text, section : Natural }
+          | Write : { contents : Text, file : Text }
+          >
+      , Dep =
+          { bound :
+              < Lower : { lower : List Natural }
+              | LowerUpper : { lower : List Natural, upper : List Natural }
+              | NoBound
+              | Upper : { upper : List Natural }
+              >
+          , name : Text
+          }
+      , EnvVar = { value : Text, var : Text }
+      , Manufacturer = < Apple | IBM | PC | Unknown >
+      , OS =
+          < AIX
+          | Android
+          | Darwin
+          | Dragonfly
+          | FreeBSD
+          | Haiku
+          | Hurd
+          | IOS
+          | Linux
+          | NetBSD
+          | NoOs
+          | OpenBSD
+          | Redox
+          | Solaris
+          | Windows
+          >
+      , Proc =
+          { arguments : List Text
+          , environment : Optional (List { value : Text, var : Text })
+          , procDir : Optional Text
+          , program : Text
+          }
+      , TargetTriple =
+          { abi :
+              Optional < GNU | GNUabi64 | GNUeabi | GNUeabihf | GNUspe | MinGw >
+          , arch :
+              < AArch
+              | Alpha
+              | Arm
+              | HPPA
+              | HPPA64
+              | M68k
+              | Mips
+              | Mips64
+              | Mips64El
+              | MipsEl
+              | MipsIsa32r6
+              | MipsIsa32r6El
+              | MipsIsa64r6
+              | MipsIsa64r6El
+              | PowerPC
+              | PowerPC64
+              | PowerPC64le
+              | RISCV64
+              | S390x
+              | SH4
+              | Sparc64
+              | X64
+              | X86
+              >
+          , manufacturer : Optional < Apple | IBM | PC | Unknown >
+          , os :
+              < AIX
+              | Android
+              | Darwin
+              | Dragonfly
+              | FreeBSD
+              | Haiku
+              | Hurd
+              | IOS
+              | Linux
+              | NetBSD
+              | NoOs
+              | OpenBSD
+              | Redox
+              | Solaris
+              | Windows
+              >
+          }
+      , VersionBound =
+          < Lower : { lower : List Natural }
+          | LowerUpper : { lower : List Natural, upper : List Natural }
+          | NoBound
+          | Upper : { upper : List Natural }
+          >
+      }
+
+let prelude =
+      { archCfg =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            merge
+              { None = cfg.buildArch
+              , Some =
+                  λ ( tgt
+                    : { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                    ) →
+                    tgt.arch
+              }
+              cfg.targetTriple
+      , autogenConfigure =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [] : List Text
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.shareDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/aclocal:${_@1}/autoconf"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/aclocal:${_@2}/autoconf:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "ACLOCAL_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = None Text
+                , program = "./autogen.sh"
+                }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      ( merge
+                          { None = [ "--prefix=${cfg.installDir}" ]
+                          , Some =
+                              λ(x : Text) → [ "--prefix=${cfg.installDir}", x ]
+                          }
+                          ( merge
+                              { None = None Text
+                              , Some =
+                                  λ ( _
+                                    : { abi :
+                                          Optional
+                                            < GNU
+                                            | GNUabi64
+                                            | GNUeabi
+                                            | GNUeabihf
+                                            | GNUspe
+                                            | MinGw
+                                            >
+                                      , arch :
+                                          < AArch
+                                          | Alpha
+                                          | Arm
+                                          | HPPA
+                                          | HPPA64
+                                          | M68k
+                                          | Mips
+                                          | Mips64
+                                          | Mips64El
+                                          | MipsEl
+                                          | MipsIsa32r6
+                                          | MipsIsa32r6El
+                                          | MipsIsa64r6
+                                          | MipsIsa64r6El
+                                          | PowerPC
+                                          | PowerPC64
+                                          | PowerPC64le
+                                          | RISCV64
+                                          | S390x
+                                          | SH4
+                                          | Sparc64
+                                          | X64
+                                          | X86
+                                          >
+                                      , manufacturer :
+                                          Optional
+                                            < Apple | IBM | PC | Unknown >
+                                      , os :
+                                          < AIX
+                                          | Android
+                                          | Darwin
+                                          | Dragonfly
+                                          | FreeBSD
+                                          | Haiku
+                                          | Hurd
+                                          | IOS
+                                          | Linux
+                                          | NetBSD
+                                          | NoOs
+                                          | OpenBSD
+                                          | Redox
+                                          | Solaris
+                                          | Windows
+                                          >
+                                      }
+                                    ) →
+                                    Some
+                                      "--host=${merge
+                                                  { AArch = "aarch64"
+                                                  , Alpha = "alpha"
+                                                  , Arm = "arm"
+                                                  , HPPA = "hppa"
+                                                  , HPPA64 = "hppa64"
+                                                  , M68k = "m68k"
+                                                  , Mips = "mips"
+                                                  , Mips64 = "mips64"
+                                                  , Mips64El = "mips64el"
+                                                  , MipsEl = "mipsel"
+                                                  , MipsIsa32r6 = "mipsisa32r6"
+                                                  , MipsIsa32r6El =
+                                                      "mipsisa32r6el"
+                                                  , MipsIsa64r6 = "mipsisa64r6"
+                                                  , MipsIsa64r6El =
+                                                      "mipsisa64r6el"
+                                                  , PowerPC = "powerpc"
+                                                  , PowerPC64 = "powerpc64"
+                                                  , PowerPC64le = "powerpc64le"
+                                                  , RISCV64 = "riscv64"
+                                                  , S390x = "s390x"
+                                                  , SH4 = "sh4"
+                                                  , Sparc64 = "sparc64"
+                                                  , X64 = "x86_64"
+                                                  , X86 = "i686"
+                                                  }
+                                                  _.arch}-${merge
+                                                              { AIX = "aix"
+                                                              , Android =
+                                                                  "android"
+                                                              , Darwin =
+                                                                  "darwin"
+                                                              , Dragonfly =
+                                                                  "dragonfly"
+                                                              , FreeBSD =
+                                                                  "freebsd"
+                                                              , Haiku = "haiku"
+                                                              , Hurd = "hurd"
+                                                              , IOS = "darwin"
+                                                              , Linux = "linux"
+                                                              , NetBSD =
+                                                                  "netbsd"
+                                                              , NoOs = "none"
+                                                              , OpenBSD =
+                                                                  "openbsd"
+                                                              , Redox = "redox"
+                                                              , Solaris =
+                                                                  "solaris"
+                                                              , Windows = "w64"
+                                                              }
+                                                              _.os}${merge
+                                                                       { None =
+                                                                           ""
+                                                                       , Some =
+                                                                           λ ( abi
+                                                                             : < GNU
+                                                                               | GNUabi64
+                                                                               | GNUeabi
+                                                                               | GNUeabihf
+                                                                               | GNUspe
+                                                                               | MinGw
+                                                                               >
+                                                                             ) →
+                                                                             "-${merge
+                                                                                   { GNU =
+                                                                                       "gnu"
+                                                                                   , GNUabi64 =
+                                                                                       "gnuabi64"
+                                                                                   , GNUeabi =
+                                                                                       "gnueabi"
+                                                                                   , GNUeabihf =
+                                                                                       "gnueabihf"
+                                                                                   , GNUspe =
+                                                                                       "gnuspe"
+                                                                                   , MinGw =
+                                                                                       "mingw32"
+                                                                                   }
+                                                                                   abi}"
+                                                                       }
+                                                                       _.abi}"
+                              }
+                              cfg.targetTriple
+                          )
+                      )
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.includeDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-I${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${if cfg.static then " -static" else ""}"
+                          , var = "CPPFLAGS"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_RUN_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , buildEnv =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              ( if    merge
+                        { AIX = True
+                        , Android = True
+                        , Darwin = True
+                        , Dragonfly = True
+                        , FreeBSD = True
+                        , Haiku = False
+                        , Hurd = True
+                        , IOS = True
+                        , Linux = True
+                        , NetBSD = True
+                        , NoOs = False
+                        , OpenBSD = True
+                        , Redox = False
+                        , Solaris = True
+                        , Windows = False
+                        }
+                        cfg.buildOS
+                then  [ { value =
+                            "${List/fold
+                                 Text
+                                 cfg.binDirs
+                                 Text
+                                 (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                 ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                        , var = "PATH"
+                        }
+                      ]
+                else  [] : List { value : Text, var : Text }
+              )
+            # [ { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          (cfg.shareDirs # cfg.linkDirs)
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty
+                                      "${_@1}/pkgconfig"
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}/pkgconfig:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "PKG_CONFIG_PATH"
+                }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          cfg.linkDirs
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty
+                                      "${_@1}/site_perl/5.30.2/${merge
+                                                                   { AArch =
+                                                                       "aarch64"
+                                                                   , Alpha =
+                                                                       "alpha"
+                                                                   , Arm = "arm"
+                                                                   , HPPA =
+                                                                       "hppa"
+                                                                   , HPPA64 =
+                                                                       "hppa64"
+                                                                   , M68k =
+                                                                       "m68k"
+                                                                   , Mips =
+                                                                       "mips"
+                                                                   , Mips64 =
+                                                                       "mips64"
+                                                                   , Mips64El =
+                                                                       "mips64el"
+                                                                   , MipsEl =
+                                                                       "mipsel"
+                                                                   , MipsIsa32r6 =
+                                                                       "mipsisa32r6"
+                                                                   , MipsIsa32r6El =
+                                                                       "mipsisa32r6el"
+                                                                   , MipsIsa64r6 =
+                                                                       "mipsisa64r6"
+                                                                   , MipsIsa64r6El =
+                                                                       "mipsisa64r6el"
+                                                                   , PowerPC =
+                                                                       "powerpc"
+                                                                   , PowerPC64 =
+                                                                       "powerpc64"
+                                                                   , PowerPC64le =
+                                                                       "powerpc64le"
+                                                                   , RISCV64 =
+                                                                       "riscv64"
+                                                                   , S390x =
+                                                                       "s390x"
+                                                                   , SH4 = "sh4"
+                                                                   , Sparc64 =
+                                                                       "sparc64"
+                                                                   , X64 =
+                                                                       "x86_64"
+                                                                   , X86 =
+                                                                       "i686"
+                                                                   }
+                                                                   cfg.buildArch}-${merge
+                                                                                      { AIX =
+                                                                                          "aix"
+                                                                                      , Android =
+                                                                                          "android"
+                                                                                      , Darwin =
+                                                                                          "darwin"
+                                                                                      , Dragonfly =
+                                                                                          "dragonfly"
+                                                                                      , FreeBSD =
+                                                                                          "freebsd"
+                                                                                      , Haiku =
+                                                                                          "haiku"
+                                                                                      , Hurd =
+                                                                                          "hurd"
+                                                                                      , IOS =
+                                                                                          "darwin"
+                                                                                      , Linux =
+                                                                                          "linux"
+                                                                                      , NetBSD =
+                                                                                          "netbsd"
+                                                                                      , NoOs =
+                                                                                          "none"
+                                                                                      , OpenBSD =
+                                                                                          "openbsd"
+                                                                                      , Redox =
+                                                                                          "redox"
+                                                                                      , Solaris =
+                                                                                          "solaris"
+                                                                                      , Windows =
+                                                                                          "w64"
+                                                                                      }
+                                                                                      cfg.buildOS}/"
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}/site_perl/5.30.2/${merge
+                                                                     { AArch =
+                                                                         "aarch64"
+                                                                     , Alpha =
+                                                                         "alpha"
+                                                                     , Arm =
+                                                                         "arm"
+                                                                     , HPPA =
+                                                                         "hppa"
+                                                                     , HPPA64 =
+                                                                         "hppa64"
+                                                                     , M68k =
+                                                                         "m68k"
+                                                                     , Mips =
+                                                                         "mips"
+                                                                     , Mips64 =
+                                                                         "mips64"
+                                                                     , Mips64El =
+                                                                         "mips64el"
+                                                                     , MipsEl =
+                                                                         "mipsel"
+                                                                     , MipsIsa32r6 =
+                                                                         "mipsisa32r6"
+                                                                     , MipsIsa32r6El =
+                                                                         "mipsisa32r6el"
+                                                                     , MipsIsa64r6 =
+                                                                         "mipsisa64r6"
+                                                                     , MipsIsa64r6El =
+                                                                         "mipsisa64r6el"
+                                                                     , PowerPC =
+                                                                         "powerpc"
+                                                                     , PowerPC64 =
+                                                                         "powerpc64"
+                                                                     , PowerPC64le =
+                                                                         "powerpc64le"
+                                                                     , RISCV64 =
+                                                                         "riscv64"
+                                                                     , S390x =
+                                                                         "s390x"
+                                                                     , SH4 =
+                                                                         "sh4"
+                                                                     , Sparc64 =
+                                                                         "sparc64"
+                                                                     , X64 =
+                                                                         "x86_64"
+                                                                     , X86 =
+                                                                         "i686"
+                                                                     }
+                                                                     cfg.buildArch}-${merge
+                                                                                        { AIX =
+                                                                                            "aix"
+                                                                                        , Android =
+                                                                                            "android"
+                                                                                        , Darwin =
+                                                                                            "darwin"
+                                                                                        , Dragonfly =
+                                                                                            "dragonfly"
+                                                                                        , FreeBSD =
+                                                                                            "freebsd"
+                                                                                        , Haiku =
+                                                                                            "haiku"
+                                                                                        , Hurd =
+                                                                                            "hurd"
+                                                                                        , IOS =
+                                                                                            "darwin"
+                                                                                        , Linux =
+                                                                                            "linux"
+                                                                                        , NetBSD =
+                                                                                            "netbsd"
+                                                                                        , NoOs =
+                                                                                            "none"
+                                                                                        , OpenBSD =
+                                                                                            "openbsd"
+                                                                                        , Redox =
+                                                                                            "redox"
+                                                                                        , Solaris =
+                                                                                            "solaris"
+                                                                                        , Windows =
+                                                                                            "w64"
+                                                                                        }
+                                                                                        cfg.buildOS}/:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "PERL5LIB"
+                }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          cfg.linkDirs
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty _@1
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "LD_LIBRARY_PATH"
+                }
+              , { value =
+                    "${merge
+                         { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                         ( List/fold
+                             Text
+                             cfg.linkDirs
+                             < Empty | NonEmpty : Text >
+                             ( λ(_ : Text) →
+                               λ(_ : < Empty | NonEmpty : Text >) →
+                                 merge
+                                   { Empty =
+                                       < Empty | NonEmpty : Text >.NonEmpty
+                                         "-L${_@1}"
+                                   , NonEmpty =
+                                       λ(_ : Text) →
+                                         < Empty | NonEmpty : Text >.NonEmpty
+                                           "-L${_@2} ${_}"
+                                   }
+                                   _
+                             )
+                             < Empty | NonEmpty : Text >.Empty
+                         )}${List/fold
+                               Text
+                               cfg.linkDirs
+                               Text
+                               ( λ(_ : Text) →
+                                 λ(_ : Text) →
+                                   "${if    merge
+                                              { AIX = False
+                                              , Android = False
+                                              , Darwin = True
+                                              , Dragonfly = False
+                                              , FreeBSD = False
+                                              , Haiku = False
+                                              , Hurd = False
+                                              , IOS = False
+                                              , Linux = False
+                                              , NetBSD = False
+                                              , NoOs = False
+                                              , OpenBSD = False
+                                              , Redox = False
+                                              , Solaris = False
+                                              , Windows = False
+                                              }
+                                              cfg.buildOS
+                                      then  ""
+                                      else  " -Wl,-rpath-link,${_@1}"}${_}"
+                               )
+                               ""}"
+                , var = "LDFLAGS"
+                }
+              ]
+      , buildWith =
+          λ(envs : List { value : Text, var : Text }) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [ "-j${Natural/show cfg.cpus}" ]
+                , environment = Some envs
+                , procDir = None Text
+                , program =
+                    merge
+                      { AIX = "make"
+                      , Android = "make"
+                      , Darwin = "make"
+                      , Dragonfly = "gmake"
+                      , FreeBSD = "gmake"
+                      , Haiku = "make"
+                      , Hurd = "make"
+                      , IOS = "make"
+                      , Linux = "make"
+                      , NetBSD = "gmake"
+                      , NoOs = "make"
+                      , OpenBSD = "gmake"
+                      , Redox = "make"
+                      , Solaris = "gmake"
+                      , Windows = "make"
+                      }
+                      cfg.buildOS
+                }
+            ]
+      , call =
+          < Call :
+              { arguments : List Text
+              , environment : Optional (List { value : Text, var : Text })
+              , procDir : Optional Text
+              , program : Text
+              }
+          | CopyFile : { dest : Text, src : Text }
+          | CreateDirectory : { dir : Text }
+          | MakeExecutable : { file : Text }
+          | Patch : { patchContents : Text }
+          | Symlink : { linkName : Text, tgt : Text }
+          | SymlinkBinary : { file : Text }
+          | SymlinkManpage : { file : Text, section : Natural }
+          | Write : { contents : Text, file : Text }
+          >.Call
+      , cmakeBuild =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                  [ "--build"
+                  , "."
+                  , "--config"
+                  , "Release"
+                  , "--"
+                  , "-j"
+                  , Natural/show cfg.cpus
+                  ]
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.includeDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "CMAKE_INCLUDE_PATH"
+                          }
+                        , { value =
+                              ( if    cfg.static
+                                then  { value =
+                                          "${List/fold
+                                               Text
+                                               cfg.linkDirs
+                                               Text
+                                               ( λ(_ : Text) →
+                                                 λ(_ : Text) →
+                                                   "${_@1}:${_}"
+                                               )
+                                               ""}/usr/local/lib:/lib:/usr/lib"
+                                      , var = "LIBRARY_PATH"
+                                      }
+                                else  { value =
+                                          merge
+                                            { Empty = ""
+                                            , NonEmpty = λ(_ : Text) → _
+                                            }
+                                            ( List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                < Empty | NonEmpty : Text >
+                                                ( λ(_ : Text) →
+                                                  λ ( _
+                                                    : < Empty
+                                                      | NonEmpty : Text
+                                                      >
+                                                    ) →
+                                                    merge
+                                                      { Empty =
+                                                          < Empty
+                                                          | NonEmpty : Text
+                                                          >.NonEmpty
+                                                            _@1
+                                                      , NonEmpty =
+                                                          λ(_ : Text) →
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              "${_@2}:${_}"
+                                                      }
+                                                      _
+                                                )
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.Empty
+                                            )
+                                      , var = "LD_LIBRARY_PATH"
+                                      }
+                              ).value
+                          , var = "CMAKE_LIBRARY_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeConfigure =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.CreateDirectory
+                { dir = "build" }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                      [ "../"
+                      , "-DCMAKE_INSTALL_PREFIX:PATH=${cfg.installDir}"
+                      , "-DCMAKE_MAKE_PROGRAM=${merge
+                                                  { AIX = "make"
+                                                  , Android = "make"
+                                                  , Darwin = "make"
+                                                  , Dragonfly = "gmake"
+                                                  , FreeBSD = "gmake"
+                                                  , Haiku = "make"
+                                                  , Hurd = "make"
+                                                  , IOS = "make"
+                                                  , Linux = "make"
+                                                  , NetBSD = "gmake"
+                                                  , NoOs = "make"
+                                                  , OpenBSD = "gmake"
+                                                  , Redox = "make"
+                                                  , Solaris = "gmake"
+                                                  , Windows = "make"
+                                                  }
+                                                  cfg.buildOS}"
+                      ]
+                    # merge
+                        { None =
+                          [ "-DCMAKE_C_COMPILER=gcc"
+                          , "-DCMAKE_CXX_COMPILER=g++"
+                          ]
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_C_COMPILER=${merge
+                                                        { AArch = "aarch64"
+                                                        , Alpha = "alpha"
+                                                        , Arm = "arm"
+                                                        , HPPA = "hppa"
+                                                        , HPPA64 = "hppa64"
+                                                        , M68k = "m68k"
+                                                        , Mips = "mips"
+                                                        , Mips64 = "mips64"
+                                                        , Mips64El = "mips64el"
+                                                        , MipsEl = "mipsel"
+                                                        , MipsIsa32r6 =
+                                                            "mipsisa32r6"
+                                                        , MipsIsa32r6El =
+                                                            "mipsisa32r6el"
+                                                        , MipsIsa64r6 =
+                                                            "mipsisa64r6"
+                                                        , MipsIsa64r6El =
+                                                            "mipsisa64r6el"
+                                                        , PowerPC = "powerpc"
+                                                        , PowerPC64 =
+                                                            "powerpc64"
+                                                        , PowerPC64le =
+                                                            "powerpc64le"
+                                                        , RISCV64 = "riscv64"
+                                                        , S390x = "s390x"
+                                                        , SH4 = "sh4"
+                                                        , Sparc64 = "sparc64"
+                                                        , X64 = "x86_64"
+                                                        , X86 = "i686"
+                                                        }
+                                                        tgt.arch}-${merge
+                                                                      { AIX =
+                                                                          "aix"
+                                                                      , Android =
+                                                                          "android"
+                                                                      , Darwin =
+                                                                          "darwin"
+                                                                      , Dragonfly =
+                                                                          "dragonfly"
+                                                                      , FreeBSD =
+                                                                          "freebsd"
+                                                                      , Haiku =
+                                                                          "haiku"
+                                                                      , Hurd =
+                                                                          "hurd"
+                                                                      , IOS =
+                                                                          "darwin"
+                                                                      , Linux =
+                                                                          "linux"
+                                                                      , NetBSD =
+                                                                          "netbsd"
+                                                                      , NoOs =
+                                                                          "none"
+                                                                      , OpenBSD =
+                                                                          "openbsd"
+                                                                      , Redox =
+                                                                          "redox"
+                                                                      , Solaris =
+                                                                          "solaris"
+                                                                      , Windows =
+                                                                          "w64"
+                                                                      }
+                                                                      tgt.os}${merge
+                                                                                 { None =
+                                                                                     ""
+                                                                                 , Some =
+                                                                                     λ ( abi
+                                                                                       : < GNU
+                                                                                         | GNUabi64
+                                                                                         | GNUeabi
+                                                                                         | GNUeabihf
+                                                                                         | GNUspe
+                                                                                         | MinGw
+                                                                                         >
+                                                                                       ) →
+                                                                                       "-${merge
+                                                                                             { GNU =
+                                                                                                 "gnu"
+                                                                                             , GNUabi64 =
+                                                                                                 "gnuabi64"
+                                                                                             , GNUeabi =
+                                                                                                 "gnueabi"
+                                                                                             , GNUeabihf =
+                                                                                                 "gnueabihf"
+                                                                                             , GNUspe =
+                                                                                                 "gnuspe"
+                                                                                             , MinGw =
+                                                                                                 "mingw32"
+                                                                                             }
+                                                                                             abi}"
+                                                                                 }
+                                                                                 tgt.abi}-gcc"
+                              , "-DCMAKE_CXX_COMPILER=${merge
+                                                          { AArch = "aarch64"
+                                                          , Alpha = "alpha"
+                                                          , Arm = "arm"
+                                                          , HPPA = "hppa"
+                                                          , HPPA64 = "hppa64"
+                                                          , M68k = "m68k"
+                                                          , Mips = "mips"
+                                                          , Mips64 = "mips64"
+                                                          , Mips64El =
+                                                              "mips64el"
+                                                          , MipsEl = "mipsel"
+                                                          , MipsIsa32r6 =
+                                                              "mipsisa32r6"
+                                                          , MipsIsa32r6El =
+                                                              "mipsisa32r6el"
+                                                          , MipsIsa64r6 =
+                                                              "mipsisa64r6"
+                                                          , MipsIsa64r6El =
+                                                              "mipsisa64r6el"
+                                                          , PowerPC = "powerpc"
+                                                          , PowerPC64 =
+                                                              "powerpc64"
+                                                          , PowerPC64le =
+                                                              "powerpc64le"
+                                                          , RISCV64 = "riscv64"
+                                                          , S390x = "s390x"
+                                                          , SH4 = "sh4"
+                                                          , Sparc64 = "sparc64"
+                                                          , X64 = "x86_64"
+                                                          , X86 = "i686"
+                                                          }
+                                                          tgt.arch}-${merge
+                                                                        { AIX =
+                                                                            "aix"
+                                                                        , Android =
+                                                                            "android"
+                                                                        , Darwin =
+                                                                            "darwin"
+                                                                        , Dragonfly =
+                                                                            "dragonfly"
+                                                                        , FreeBSD =
+                                                                            "freebsd"
+                                                                        , Haiku =
+                                                                            "haiku"
+                                                                        , Hurd =
+                                                                            "hurd"
+                                                                        , IOS =
+                                                                            "darwin"
+                                                                        , Linux =
+                                                                            "linux"
+                                                                        , NetBSD =
+                                                                            "netbsd"
+                                                                        , NoOs =
+                                                                            "none"
+                                                                        , OpenBSD =
+                                                                            "openbsd"
+                                                                        , Redox =
+                                                                            "redox"
+                                                                        , Solaris =
+                                                                            "solaris"
+                                                                        , Windows =
+                                                                            "w64"
+                                                                        }
+                                                                        tgt.os}${merge
+                                                                                   { None =
+                                                                                       ""
+                                                                                   , Some =
+                                                                                       λ ( abi
+                                                                                         : < GNU
+                                                                                           | GNUabi64
+                                                                                           | GNUeabi
+                                                                                           | GNUeabihf
+                                                                                           | GNUspe
+                                                                                           | MinGw
+                                                                                           >
+                                                                                         ) →
+                                                                                         "-${merge
+                                                                                               { GNU =
+                                                                                                   "gnu"
+                                                                                               , GNUabi64 =
+                                                                                                   "gnuabi64"
+                                                                                               , GNUeabi =
+                                                                                                   "gnueabi"
+                                                                                               , GNUeabihf =
+                                                                                                   "gnueabihf"
+                                                                                               , GNUspe =
+                                                                                                   "gnuspe"
+                                                                                               , MinGw =
+                                                                                                   "mingw32"
+                                                                                               }
+                                                                                               abi}"
+                                                                                   }
+                                                                                   tgt.abi}-g++"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # merge
+                        { None = [] : List Text
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_SYSTEM_NAME=${merge
+                                                         { AIX = "AIX"
+                                                         , Android = "Android"
+                                                         , Darwin = "Darwin"
+                                                         , Dragonfly = "BSD"
+                                                         , FreeBSD = "BSD"
+                                                         , Haiku = "Haiku"
+                                                         , Hurd = "Hurd"
+                                                         , IOS = "Darwin"
+                                                         , Linux = "Linux"
+                                                         , NetBSD = "BSD"
+                                                         , NoOs = "Generic"
+                                                         , OpenBSD = "BSD"
+                                                         , Redox = "Redox"
+                                                         , Solaris = "Solaris"
+                                                         , Windows = "Windows"
+                                                         }
+                                                         tgt.os}"
+                              ]
+                        }
+                        cfg.targetTriple
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.includeDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "CMAKE_INCLUDE_PATH"
+                          }
+                        , { value =
+                              ( if    cfg.static
+                                then  { value =
+                                          "${List/fold
+                                               Text
+                                               cfg.linkDirs
+                                               Text
+                                               ( λ(_ : Text) →
+                                                 λ(_ : Text) →
+                                                   "${_@1}:${_}"
+                                               )
+                                               ""}/usr/local/lib:/lib:/usr/lib"
+                                      , var = "LIBRARY_PATH"
+                                      }
+                                else  { value =
+                                          merge
+                                            { Empty = ""
+                                            , NonEmpty = λ(_ : Text) → _
+                                            }
+                                            ( List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                < Empty | NonEmpty : Text >
+                                                ( λ(_ : Text) →
+                                                  λ ( _
+                                                    : < Empty
+                                                      | NonEmpty : Text
+                                                      >
+                                                    ) →
+                                                    merge
+                                                      { Empty =
+                                                          < Empty
+                                                          | NonEmpty : Text
+                                                          >.NonEmpty
+                                                            _@1
+                                                      , NonEmpty =
+                                                          λ(_ : Text) →
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              "${_@2}:${_}"
+                                                      }
+                                                      _
+                                                )
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.Empty
+                                            )
+                                      , var = "LD_LIBRARY_PATH"
+                                      }
+                              ).value
+                          , var = "CMAKE_LIBRARY_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeConfigureGeneral =
+          λ ( envVars
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              } →
+                Optional (List { value : Text, var : Text })
+            ) →
+          λ(flags : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.CreateDirectory
+                { dir = "build" }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                      [ "../"
+                      , "-DCMAKE_INSTALL_PREFIX:PATH=${cfg.installDir}"
+                      , "-DCMAKE_MAKE_PROGRAM=${merge
+                                                  { AIX = "make"
+                                                  , Android = "make"
+                                                  , Darwin = "make"
+                                                  , Dragonfly = "gmake"
+                                                  , FreeBSD = "gmake"
+                                                  , Haiku = "make"
+                                                  , Hurd = "make"
+                                                  , IOS = "make"
+                                                  , Linux = "make"
+                                                  , NetBSD = "gmake"
+                                                  , NoOs = "make"
+                                                  , OpenBSD = "gmake"
+                                                  , Redox = "make"
+                                                  , Solaris = "gmake"
+                                                  , Windows = "make"
+                                                  }
+                                                  cfg.buildOS}"
+                      ]
+                    # merge
+                        { None =
+                          [ "-DCMAKE_C_COMPILER=gcc"
+                          , "-DCMAKE_CXX_COMPILER=g++"
+                          ]
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_C_COMPILER=${merge
+                                                        { AArch = "aarch64"
+                                                        , Alpha = "alpha"
+                                                        , Arm = "arm"
+                                                        , HPPA = "hppa"
+                                                        , HPPA64 = "hppa64"
+                                                        , M68k = "m68k"
+                                                        , Mips = "mips"
+                                                        , Mips64 = "mips64"
+                                                        , Mips64El = "mips64el"
+                                                        , MipsEl = "mipsel"
+                                                        , MipsIsa32r6 =
+                                                            "mipsisa32r6"
+                                                        , MipsIsa32r6El =
+                                                            "mipsisa32r6el"
+                                                        , MipsIsa64r6 =
+                                                            "mipsisa64r6"
+                                                        , MipsIsa64r6El =
+                                                            "mipsisa64r6el"
+                                                        , PowerPC = "powerpc"
+                                                        , PowerPC64 =
+                                                            "powerpc64"
+                                                        , PowerPC64le =
+                                                            "powerpc64le"
+                                                        , RISCV64 = "riscv64"
+                                                        , S390x = "s390x"
+                                                        , SH4 = "sh4"
+                                                        , Sparc64 = "sparc64"
+                                                        , X64 = "x86_64"
+                                                        , X86 = "i686"
+                                                        }
+                                                        tgt.arch}-${merge
+                                                                      { AIX =
+                                                                          "aix"
+                                                                      , Android =
+                                                                          "android"
+                                                                      , Darwin =
+                                                                          "darwin"
+                                                                      , Dragonfly =
+                                                                          "dragonfly"
+                                                                      , FreeBSD =
+                                                                          "freebsd"
+                                                                      , Haiku =
+                                                                          "haiku"
+                                                                      , Hurd =
+                                                                          "hurd"
+                                                                      , IOS =
+                                                                          "darwin"
+                                                                      , Linux =
+                                                                          "linux"
+                                                                      , NetBSD =
+                                                                          "netbsd"
+                                                                      , NoOs =
+                                                                          "none"
+                                                                      , OpenBSD =
+                                                                          "openbsd"
+                                                                      , Redox =
+                                                                          "redox"
+                                                                      , Solaris =
+                                                                          "solaris"
+                                                                      , Windows =
+                                                                          "w64"
+                                                                      }
+                                                                      tgt.os}${merge
+                                                                                 { None =
+                                                                                     ""
+                                                                                 , Some =
+                                                                                     λ ( abi
+                                                                                       : < GNU
+                                                                                         | GNUabi64
+                                                                                         | GNUeabi
+                                                                                         | GNUeabihf
+                                                                                         | GNUspe
+                                                                                         | MinGw
+                                                                                         >
+                                                                                       ) →
+                                                                                       "-${merge
+                                                                                             { GNU =
+                                                                                                 "gnu"
+                                                                                             , GNUabi64 =
+                                                                                                 "gnuabi64"
+                                                                                             , GNUeabi =
+                                                                                                 "gnueabi"
+                                                                                             , GNUeabihf =
+                                                                                                 "gnueabihf"
+                                                                                             , GNUspe =
+                                                                                                 "gnuspe"
+                                                                                             , MinGw =
+                                                                                                 "mingw32"
+                                                                                             }
+                                                                                             abi}"
+                                                                                 }
+                                                                                 tgt.abi}-gcc"
+                              , "-DCMAKE_CXX_COMPILER=${merge
+                                                          { AArch = "aarch64"
+                                                          , Alpha = "alpha"
+                                                          , Arm = "arm"
+                                                          , HPPA = "hppa"
+                                                          , HPPA64 = "hppa64"
+                                                          , M68k = "m68k"
+                                                          , Mips = "mips"
+                                                          , Mips64 = "mips64"
+                                                          , Mips64El =
+                                                              "mips64el"
+                                                          , MipsEl = "mipsel"
+                                                          , MipsIsa32r6 =
+                                                              "mipsisa32r6"
+                                                          , MipsIsa32r6El =
+                                                              "mipsisa32r6el"
+                                                          , MipsIsa64r6 =
+                                                              "mipsisa64r6"
+                                                          , MipsIsa64r6El =
+                                                              "mipsisa64r6el"
+                                                          , PowerPC = "powerpc"
+                                                          , PowerPC64 =
+                                                              "powerpc64"
+                                                          , PowerPC64le =
+                                                              "powerpc64le"
+                                                          , RISCV64 = "riscv64"
+                                                          , S390x = "s390x"
+                                                          , SH4 = "sh4"
+                                                          , Sparc64 = "sparc64"
+                                                          , X64 = "x86_64"
+                                                          , X86 = "i686"
+                                                          }
+                                                          tgt.arch}-${merge
+                                                                        { AIX =
+                                                                            "aix"
+                                                                        , Android =
+                                                                            "android"
+                                                                        , Darwin =
+                                                                            "darwin"
+                                                                        , Dragonfly =
+                                                                            "dragonfly"
+                                                                        , FreeBSD =
+                                                                            "freebsd"
+                                                                        , Haiku =
+                                                                            "haiku"
+                                                                        , Hurd =
+                                                                            "hurd"
+                                                                        , IOS =
+                                                                            "darwin"
+                                                                        , Linux =
+                                                                            "linux"
+                                                                        , NetBSD =
+                                                                            "netbsd"
+                                                                        , NoOs =
+                                                                            "none"
+                                                                        , OpenBSD =
+                                                                            "openbsd"
+                                                                        , Redox =
+                                                                            "redox"
+                                                                        , Solaris =
+                                                                            "solaris"
+                                                                        , Windows =
+                                                                            "w64"
+                                                                        }
+                                                                        tgt.os}${merge
+                                                                                   { None =
+                                                                                       ""
+                                                                                   , Some =
+                                                                                       λ ( abi
+                                                                                         : < GNU
+                                                                                           | GNUabi64
+                                                                                           | GNUeabi
+                                                                                           | GNUeabihf
+                                                                                           | GNUspe
+                                                                                           | MinGw
+                                                                                           >
+                                                                                         ) →
+                                                                                         "-${merge
+                                                                                               { GNU =
+                                                                                                   "gnu"
+                                                                                               , GNUabi64 =
+                                                                                                   "gnuabi64"
+                                                                                               , GNUeabi =
+                                                                                                   "gnueabi"
+                                                                                               , GNUeabihf =
+                                                                                                   "gnueabihf"
+                                                                                               , GNUspe =
+                                                                                                   "gnuspe"
+                                                                                               , MinGw =
+                                                                                                   "mingw32"
+                                                                                               }
+                                                                                               abi}"
+                                                                                   }
+                                                                                   tgt.abi}-g++"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # merge
+                        { None = [] : List Text
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_SYSTEM_NAME=${merge
+                                                         { AIX = "AIX"
+                                                         , Android = "Android"
+                                                         , Darwin = "Darwin"
+                                                         , Dragonfly = "BSD"
+                                                         , FreeBSD = "BSD"
+                                                         , Haiku = "Haiku"
+                                                         , Hurd = "Hurd"
+                                                         , IOS = "Darwin"
+                                                         , Linux = "Linux"
+                                                         , NetBSD = "BSD"
+                                                         , NoOs = "Generic"
+                                                         , OpenBSD = "BSD"
+                                                         , Redox = "Redox"
+                                                         , Solaris = "Solaris"
+                                                         , Windows = "Windows"
+                                                         }
+                                                         tgt.os}"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # flags
+                , environment = envVars cfg
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeConfigureNinja =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.CreateDirectory
+                { dir = "build" }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                      [ "../"
+                      , "-DCMAKE_INSTALL_PREFIX:PATH=${cfg.installDir}"
+                      , "-G"
+                      , "Ninja"
+                      ]
+                    # merge
+                        { None = [] : List Text
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_C_COMPILER=${merge
+                                                        { AArch = "aarch64"
+                                                        , Alpha = "alpha"
+                                                        , Arm = "arm"
+                                                        , HPPA = "hppa"
+                                                        , HPPA64 = "hppa64"
+                                                        , M68k = "m68k"
+                                                        , Mips = "mips"
+                                                        , Mips64 = "mips64"
+                                                        , Mips64El = "mips64el"
+                                                        , MipsEl = "mipsel"
+                                                        , MipsIsa32r6 =
+                                                            "mipsisa32r6"
+                                                        , MipsIsa32r6El =
+                                                            "mipsisa32r6el"
+                                                        , MipsIsa64r6 =
+                                                            "mipsisa64r6"
+                                                        , MipsIsa64r6El =
+                                                            "mipsisa64r6el"
+                                                        , PowerPC = "powerpc"
+                                                        , PowerPC64 =
+                                                            "powerpc64"
+                                                        , PowerPC64le =
+                                                            "powerpc64le"
+                                                        , RISCV64 = "riscv64"
+                                                        , S390x = "s390x"
+                                                        , SH4 = "sh4"
+                                                        , Sparc64 = "sparc64"
+                                                        , X64 = "x86_64"
+                                                        , X86 = "i686"
+                                                        }
+                                                        tgt.arch}-${merge
+                                                                      { AIX =
+                                                                          "aix"
+                                                                      , Android =
+                                                                          "android"
+                                                                      , Darwin =
+                                                                          "darwin"
+                                                                      , Dragonfly =
+                                                                          "dragonfly"
+                                                                      , FreeBSD =
+                                                                          "freebsd"
+                                                                      , Haiku =
+                                                                          "haiku"
+                                                                      , Hurd =
+                                                                          "hurd"
+                                                                      , IOS =
+                                                                          "darwin"
+                                                                      , Linux =
+                                                                          "linux"
+                                                                      , NetBSD =
+                                                                          "netbsd"
+                                                                      , NoOs =
+                                                                          "none"
+                                                                      , OpenBSD =
+                                                                          "openbsd"
+                                                                      , Redox =
+                                                                          "redox"
+                                                                      , Solaris =
+                                                                          "solaris"
+                                                                      , Windows =
+                                                                          "w64"
+                                                                      }
+                                                                      tgt.os}${merge
+                                                                                 { None =
+                                                                                     ""
+                                                                                 , Some =
+                                                                                     λ ( abi
+                                                                                       : < GNU
+                                                                                         | GNUabi64
+                                                                                         | GNUeabi
+                                                                                         | GNUeabihf
+                                                                                         | GNUspe
+                                                                                         | MinGw
+                                                                                         >
+                                                                                       ) →
+                                                                                       "-${merge
+                                                                                             { GNU =
+                                                                                                 "gnu"
+                                                                                             , GNUabi64 =
+                                                                                                 "gnuabi64"
+                                                                                             , GNUeabi =
+                                                                                                 "gnueabi"
+                                                                                             , GNUeabihf =
+                                                                                                 "gnueabihf"
+                                                                                             , GNUspe =
+                                                                                                 "gnuspe"
+                                                                                             , MinGw =
+                                                                                                 "mingw32"
+                                                                                             }
+                                                                                             abi}"
+                                                                                 }
+                                                                                 tgt.abi}-gcc"
+                              , "-DCMAKE_CXX_COMPILER=${merge
+                                                          { AArch = "aarch64"
+                                                          , Alpha = "alpha"
+                                                          , Arm = "arm"
+                                                          , HPPA = "hppa"
+                                                          , HPPA64 = "hppa64"
+                                                          , M68k = "m68k"
+                                                          , Mips = "mips"
+                                                          , Mips64 = "mips64"
+                                                          , Mips64El =
+                                                              "mips64el"
+                                                          , MipsEl = "mipsel"
+                                                          , MipsIsa32r6 =
+                                                              "mipsisa32r6"
+                                                          , MipsIsa32r6El =
+                                                              "mipsisa32r6el"
+                                                          , MipsIsa64r6 =
+                                                              "mipsisa64r6"
+                                                          , MipsIsa64r6El =
+                                                              "mipsisa64r6el"
+                                                          , PowerPC = "powerpc"
+                                                          , PowerPC64 =
+                                                              "powerpc64"
+                                                          , PowerPC64le =
+                                                              "powerpc64le"
+                                                          , RISCV64 = "riscv64"
+                                                          , S390x = "s390x"
+                                                          , SH4 = "sh4"
+                                                          , Sparc64 = "sparc64"
+                                                          , X64 = "x86_64"
+                                                          , X86 = "i686"
+                                                          }
+                                                          tgt.arch}-${merge
+                                                                        { AIX =
+                                                                            "aix"
+                                                                        , Android =
+                                                                            "android"
+                                                                        , Darwin =
+                                                                            "darwin"
+                                                                        , Dragonfly =
+                                                                            "dragonfly"
+                                                                        , FreeBSD =
+                                                                            "freebsd"
+                                                                        , Haiku =
+                                                                            "haiku"
+                                                                        , Hurd =
+                                                                            "hurd"
+                                                                        , IOS =
+                                                                            "darwin"
+                                                                        , Linux =
+                                                                            "linux"
+                                                                        , NetBSD =
+                                                                            "netbsd"
+                                                                        , NoOs =
+                                                                            "none"
+                                                                        , OpenBSD =
+                                                                            "openbsd"
+                                                                        , Redox =
+                                                                            "redox"
+                                                                        , Solaris =
+                                                                            "solaris"
+                                                                        , Windows =
+                                                                            "w64"
+                                                                        }
+                                                                        tgt.os}${merge
+                                                                                   { None =
+                                                                                       ""
+                                                                                   , Some =
+                                                                                       λ ( abi
+                                                                                         : < GNU
+                                                                                           | GNUabi64
+                                                                                           | GNUeabi
+                                                                                           | GNUeabihf
+                                                                                           | GNUspe
+                                                                                           | MinGw
+                                                                                           >
+                                                                                         ) →
+                                                                                         "-${merge
+                                                                                               { GNU =
+                                                                                                   "gnu"
+                                                                                               , GNUabi64 =
+                                                                                                   "gnuabi64"
+                                                                                               , GNUeabi =
+                                                                                                   "gnueabi"
+                                                                                               , GNUeabihf =
+                                                                                                   "gnueabihf"
+                                                                                               , GNUspe =
+                                                                                                   "gnuspe"
+                                                                                               , MinGw =
+                                                                                                   "mingw32"
+                                                                                               }
+                                                                                               abi}"
+                                                                                   }
+                                                                                   tgt.abi}-g++"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # merge
+                        { None = [] : List Text
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_SYSTEM_NAME=${merge
+                                                         { AIX = "AIX"
+                                                         , Android = "Android"
+                                                         , Darwin = "Darwin"
+                                                         , Dragonfly = "BSD"
+                                                         , FreeBSD = "BSD"
+                                                         , Haiku = "Haiku"
+                                                         , Hurd = "Hurd"
+                                                         , IOS = "Darwin"
+                                                         , Linux = "Linux"
+                                                         , NetBSD = "BSD"
+                                                         , NoOs = "Generic"
+                                                         , OpenBSD = "BSD"
+                                                         , Redox = "Redox"
+                                                         , Solaris = "Solaris"
+                                                         , Windows = "Windows"
+                                                         }
+                                                         tgt.os}"
+                              ]
+                        }
+                        cfg.targetTriple
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.includeDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "CMAKE_INCLUDE_PATH"
+                          }
+                        , { value =
+                              ( if    cfg.static
+                                then  { value =
+                                          "${List/fold
+                                               Text
+                                               cfg.linkDirs
+                                               Text
+                                               ( λ(_ : Text) →
+                                                 λ(_ : Text) →
+                                                   "${_@1}:${_}"
+                                               )
+                                               ""}/usr/local/lib:/lib:/usr/lib"
+                                      , var = "LIBRARY_PATH"
+                                      }
+                                else  { value =
+                                          merge
+                                            { Empty = ""
+                                            , NonEmpty = λ(_ : Text) → _
+                                            }
+                                            ( List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                < Empty | NonEmpty : Text >
+                                                ( λ(_ : Text) →
+                                                  λ ( _
+                                                    : < Empty
+                                                      | NonEmpty : Text
+                                                      >
+                                                    ) →
+                                                    merge
+                                                      { Empty =
+                                                          < Empty
+                                                          | NonEmpty : Text
+                                                          >.NonEmpty
+                                                            _@1
+                                                      , NonEmpty =
+                                                          λ(_ : Text) →
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              "${_@2}:${_}"
+                                                      }
+                                                      _
+                                                )
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.Empty
+                                            )
+                                      , var = "LD_LIBRARY_PATH"
+                                      }
+                              ).value
+                          , var = "CMAKE_LIBRARY_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeConfigureWithFlags =
+          λ(flags : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.CreateDirectory
+                { dir = "build" }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                      [ "../"
+                      , "-DCMAKE_INSTALL_PREFIX:PATH=${cfg.installDir}"
+                      , "-DCMAKE_MAKE_PROGRAM=${merge
+                                                  { AIX = "make"
+                                                  , Android = "make"
+                                                  , Darwin = "make"
+                                                  , Dragonfly = "gmake"
+                                                  , FreeBSD = "gmake"
+                                                  , Haiku = "make"
+                                                  , Hurd = "make"
+                                                  , IOS = "make"
+                                                  , Linux = "make"
+                                                  , NetBSD = "gmake"
+                                                  , NoOs = "make"
+                                                  , OpenBSD = "gmake"
+                                                  , Redox = "make"
+                                                  , Solaris = "gmake"
+                                                  , Windows = "make"
+                                                  }
+                                                  cfg.buildOS}"
+                      ]
+                    # merge
+                        { None =
+                          [ "-DCMAKE_C_COMPILER=gcc"
+                          , "-DCMAKE_CXX_COMPILER=g++"
+                          ]
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_C_COMPILER=${merge
+                                                        { AArch = "aarch64"
+                                                        , Alpha = "alpha"
+                                                        , Arm = "arm"
+                                                        , HPPA = "hppa"
+                                                        , HPPA64 = "hppa64"
+                                                        , M68k = "m68k"
+                                                        , Mips = "mips"
+                                                        , Mips64 = "mips64"
+                                                        , Mips64El = "mips64el"
+                                                        , MipsEl = "mipsel"
+                                                        , MipsIsa32r6 =
+                                                            "mipsisa32r6"
+                                                        , MipsIsa32r6El =
+                                                            "mipsisa32r6el"
+                                                        , MipsIsa64r6 =
+                                                            "mipsisa64r6"
+                                                        , MipsIsa64r6El =
+                                                            "mipsisa64r6el"
+                                                        , PowerPC = "powerpc"
+                                                        , PowerPC64 =
+                                                            "powerpc64"
+                                                        , PowerPC64le =
+                                                            "powerpc64le"
+                                                        , RISCV64 = "riscv64"
+                                                        , S390x = "s390x"
+                                                        , SH4 = "sh4"
+                                                        , Sparc64 = "sparc64"
+                                                        , X64 = "x86_64"
+                                                        , X86 = "i686"
+                                                        }
+                                                        tgt.arch}-${merge
+                                                                      { AIX =
+                                                                          "aix"
+                                                                      , Android =
+                                                                          "android"
+                                                                      , Darwin =
+                                                                          "darwin"
+                                                                      , Dragonfly =
+                                                                          "dragonfly"
+                                                                      , FreeBSD =
+                                                                          "freebsd"
+                                                                      , Haiku =
+                                                                          "haiku"
+                                                                      , Hurd =
+                                                                          "hurd"
+                                                                      , IOS =
+                                                                          "darwin"
+                                                                      , Linux =
+                                                                          "linux"
+                                                                      , NetBSD =
+                                                                          "netbsd"
+                                                                      , NoOs =
+                                                                          "none"
+                                                                      , OpenBSD =
+                                                                          "openbsd"
+                                                                      , Redox =
+                                                                          "redox"
+                                                                      , Solaris =
+                                                                          "solaris"
+                                                                      , Windows =
+                                                                          "w64"
+                                                                      }
+                                                                      tgt.os}${merge
+                                                                                 { None =
+                                                                                     ""
+                                                                                 , Some =
+                                                                                     λ ( abi
+                                                                                       : < GNU
+                                                                                         | GNUabi64
+                                                                                         | GNUeabi
+                                                                                         | GNUeabihf
+                                                                                         | GNUspe
+                                                                                         | MinGw
+                                                                                         >
+                                                                                       ) →
+                                                                                       "-${merge
+                                                                                             { GNU =
+                                                                                                 "gnu"
+                                                                                             , GNUabi64 =
+                                                                                                 "gnuabi64"
+                                                                                             , GNUeabi =
+                                                                                                 "gnueabi"
+                                                                                             , GNUeabihf =
+                                                                                                 "gnueabihf"
+                                                                                             , GNUspe =
+                                                                                                 "gnuspe"
+                                                                                             , MinGw =
+                                                                                                 "mingw32"
+                                                                                             }
+                                                                                             abi}"
+                                                                                 }
+                                                                                 tgt.abi}-gcc"
+                              , "-DCMAKE_CXX_COMPILER=${merge
+                                                          { AArch = "aarch64"
+                                                          , Alpha = "alpha"
+                                                          , Arm = "arm"
+                                                          , HPPA = "hppa"
+                                                          , HPPA64 = "hppa64"
+                                                          , M68k = "m68k"
+                                                          , Mips = "mips"
+                                                          , Mips64 = "mips64"
+                                                          , Mips64El =
+                                                              "mips64el"
+                                                          , MipsEl = "mipsel"
+                                                          , MipsIsa32r6 =
+                                                              "mipsisa32r6"
+                                                          , MipsIsa32r6El =
+                                                              "mipsisa32r6el"
+                                                          , MipsIsa64r6 =
+                                                              "mipsisa64r6"
+                                                          , MipsIsa64r6El =
+                                                              "mipsisa64r6el"
+                                                          , PowerPC = "powerpc"
+                                                          , PowerPC64 =
+                                                              "powerpc64"
+                                                          , PowerPC64le =
+                                                              "powerpc64le"
+                                                          , RISCV64 = "riscv64"
+                                                          , S390x = "s390x"
+                                                          , SH4 = "sh4"
+                                                          , Sparc64 = "sparc64"
+                                                          , X64 = "x86_64"
+                                                          , X86 = "i686"
+                                                          }
+                                                          tgt.arch}-${merge
+                                                                        { AIX =
+                                                                            "aix"
+                                                                        , Android =
+                                                                            "android"
+                                                                        , Darwin =
+                                                                            "darwin"
+                                                                        , Dragonfly =
+                                                                            "dragonfly"
+                                                                        , FreeBSD =
+                                                                            "freebsd"
+                                                                        , Haiku =
+                                                                            "haiku"
+                                                                        , Hurd =
+                                                                            "hurd"
+                                                                        , IOS =
+                                                                            "darwin"
+                                                                        , Linux =
+                                                                            "linux"
+                                                                        , NetBSD =
+                                                                            "netbsd"
+                                                                        , NoOs =
+                                                                            "none"
+                                                                        , OpenBSD =
+                                                                            "openbsd"
+                                                                        , Redox =
+                                                                            "redox"
+                                                                        , Solaris =
+                                                                            "solaris"
+                                                                        , Windows =
+                                                                            "w64"
+                                                                        }
+                                                                        tgt.os}${merge
+                                                                                   { None =
+                                                                                       ""
+                                                                                   , Some =
+                                                                                       λ ( abi
+                                                                                         : < GNU
+                                                                                           | GNUabi64
+                                                                                           | GNUeabi
+                                                                                           | GNUeabihf
+                                                                                           | GNUspe
+                                                                                           | MinGw
+                                                                                           >
+                                                                                         ) →
+                                                                                         "-${merge
+                                                                                               { GNU =
+                                                                                                   "gnu"
+                                                                                               , GNUabi64 =
+                                                                                                   "gnuabi64"
+                                                                                               , GNUeabi =
+                                                                                                   "gnueabi"
+                                                                                               , GNUeabihf =
+                                                                                                   "gnueabihf"
+                                                                                               , GNUspe =
+                                                                                                   "gnuspe"
+                                                                                               , MinGw =
+                                                                                                   "mingw32"
+                                                                                               }
+                                                                                               abi}"
+                                                                                   }
+                                                                                   tgt.abi}-g++"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # merge
+                        { None = [] : List Text
+                        , Some =
+                            λ ( tgt
+                              : { abi :
+                                    Optional
+                                      < GNU
+                                      | GNUabi64
+                                      | GNUeabi
+                                      | GNUeabihf
+                                      | GNUspe
+                                      | MinGw
+                                      >
+                                , arch :
+                                    < AArch
+                                    | Alpha
+                                    | Arm
+                                    | HPPA
+                                    | HPPA64
+                                    | M68k
+                                    | Mips
+                                    | Mips64
+                                    | Mips64El
+                                    | MipsEl
+                                    | MipsIsa32r6
+                                    | MipsIsa32r6El
+                                    | MipsIsa64r6
+                                    | MipsIsa64r6El
+                                    | PowerPC
+                                    | PowerPC64
+                                    | PowerPC64le
+                                    | RISCV64
+                                    | S390x
+                                    | SH4
+                                    | Sparc64
+                                    | X64
+                                    | X86
+                                    >
+                                , manufacturer :
+                                    Optional < Apple | IBM | PC | Unknown >
+                                , os :
+                                    < AIX
+                                    | Android
+                                    | Darwin
+                                    | Dragonfly
+                                    | FreeBSD
+                                    | Haiku
+                                    | Hurd
+                                    | IOS
+                                    | Linux
+                                    | NetBSD
+                                    | NoOs
+                                    | OpenBSD
+                                    | Redox
+                                    | Solaris
+                                    | Windows
+                                    >
+                                }
+                              ) →
+                              [ "-DCMAKE_SYSTEM_NAME=${merge
+                                                         { AIX = "AIX"
+                                                         , Android = "Android"
+                                                         , Darwin = "Darwin"
+                                                         , Dragonfly = "BSD"
+                                                         , FreeBSD = "BSD"
+                                                         , Haiku = "Haiku"
+                                                         , Hurd = "Hurd"
+                                                         , IOS = "Darwin"
+                                                         , Linux = "Linux"
+                                                         , NetBSD = "BSD"
+                                                         , NoOs = "Generic"
+                                                         , OpenBSD = "BSD"
+                                                         , Redox = "Redox"
+                                                         , Solaris = "Solaris"
+                                                         , Windows = "Windows"
+                                                         }
+                                                         tgt.os}"
+                              ]
+                        }
+                        cfg.targetTriple
+                    # flags
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.includeDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "CMAKE_INCLUDE_PATH"
+                          }
+                        , { value =
+                              ( if    cfg.static
+                                then  { value =
+                                          "${List/fold
+                                               Text
+                                               cfg.linkDirs
+                                               Text
+                                               ( λ(_ : Text) →
+                                                 λ(_ : Text) →
+                                                   "${_@1}:${_}"
+                                               )
+                                               ""}/usr/local/lib:/lib:/usr/lib"
+                                      , var = "LIBRARY_PATH"
+                                      }
+                                else  { value =
+                                          merge
+                                            { Empty = ""
+                                            , NonEmpty = λ(_ : Text) → _
+                                            }
+                                            ( List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                < Empty | NonEmpty : Text >
+                                                ( λ(_ : Text) →
+                                                  λ ( _
+                                                    : < Empty
+                                                      | NonEmpty : Text
+                                                      >
+                                                    ) →
+                                                    merge
+                                                      { Empty =
+                                                          < Empty
+                                                          | NonEmpty : Text
+                                                          >.NonEmpty
+                                                            _@1
+                                                      , NonEmpty =
+                                                          λ(_ : Text) →
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              "${_@2}:${_}"
+                                                      }
+                                                      _
+                                                )
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.Empty
+                                            )
+                                      , var = "LD_LIBRARY_PATH"
+                                      }
+                              ).value
+                          , var = "CMAKE_LIBRARY_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeEnv =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              [ { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          (cfg.shareDirs # cfg.linkDirs)
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty
+                                      "${_@1}/pkgconfig"
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}/pkgconfig:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "PKG_CONFIG_PATH"
+                }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          cfg.includeDirs
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty _@1
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "CMAKE_INCLUDE_PATH"
+                }
+              , { value =
+                    ( if    cfg.static
+                      then  { value =
+                                "${List/fold
+                                     Text
+                                     cfg.linkDirs
+                                     Text
+                                     (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                     ""}/usr/local/lib:/lib:/usr/lib"
+                            , var = "LIBRARY_PATH"
+                            }
+                      else  { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_LIBRARY_PATH"
+                            }
+                    ).value
+                , var = "CMAKE_LIBRARY_PATH"
+                }
+              ]
+            # ( if    merge
+                        { AIX = True
+                        , Android = True
+                        , Darwin = True
+                        , Dragonfly = True
+                        , FreeBSD = True
+                        , Haiku = False
+                        , Hurd = True
+                        , IOS = True
+                        , Linux = True
+                        , NetBSD = True
+                        , NoOs = False
+                        , OpenBSD = True
+                        , Redox = False
+                        , Solaris = True
+                        , Windows = False
+                        }
+                        cfg.buildOS
+                then  [ { value =
+                            "${List/fold
+                                 Text
+                                 cfg.binDirs
+                                 Text
+                                 (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                 ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                        , var = "PATH"
+                        }
+                      ]
+                else  [] : List { value : Text, var : Text }
+              )
+      , cmakeInstall =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                  [ "--build"
+                  , "."
+                  , "--target"
+                  , "install"
+                  , "--config"
+                  , "Release"
+                  ]
+                , environment = Some
+                    (   [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.includeDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "CMAKE_INCLUDE_PATH"
+                          }
+                        , { value =
+                              ( if    cfg.static
+                                then  { value =
+                                          "${List/fold
+                                               Text
+                                               cfg.linkDirs
+                                               Text
+                                               ( λ(_ : Text) →
+                                                 λ(_ : Text) →
+                                                   "${_@1}:${_}"
+                                               )
+                                               ""}/usr/local/lib:/lib:/usr/lib"
+                                      , var = "LIBRARY_PATH"
+                                      }
+                                else  { value =
+                                          merge
+                                            { Empty = ""
+                                            , NonEmpty = λ(_ : Text) → _
+                                            }
+                                            ( List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                < Empty | NonEmpty : Text >
+                                                ( λ(_ : Text) →
+                                                  λ ( _
+                                                    : < Empty
+                                                      | NonEmpty : Text
+                                                      >
+                                                    ) →
+                                                    merge
+                                                      { Empty =
+                                                          < Empty
+                                                          | NonEmpty : Text
+                                                          >.NonEmpty
+                                                            _@1
+                                                      , NonEmpty =
+                                                          λ(_ : Text) →
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              "${_@2}:${_}"
+                                                      }
+                                                      _
+                                                )
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.Empty
+                                            )
+                                      , var = "LD_LIBRARY_PATH"
+                                      }
+                              ).value
+                          , var = "CMAKE_LIBRARY_PATH"
+                          }
+                        ]
+                      # ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                    )
+                , procDir = Some "build"
+                , program = "cmake"
+                }
+            ]
+      , cmakeInstallWithBinaries =
+          λ(bins : List Text) →
+          λ ( installVars
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                    [ "--build"
+                    , "."
+                    , "--target"
+                    , "install"
+                    , "--config"
+                    , "Release"
+                    ]
+                  , environment = Some
+                      (   [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (   installVars.shareDirs
+                                        # installVars.linkDirs
+                                      )
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      installVars.includeDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "CMAKE_INCLUDE_PATH"
+                            }
+                          , { value =
+                                ( if    installVars.static
+                                  then  { value =
+                                            "${List/fold
+                                                 Text
+                                                 installVars.linkDirs
+                                                 Text
+                                                 ( λ(_ : Text) →
+                                                   λ(_ : Text) →
+                                                     "${_@1}:${_}"
+                                                 )
+                                                 ""}/usr/local/lib:/lib:/usr/lib"
+                                        , var = "LIBRARY_PATH"
+                                        }
+                                  else  { value =
+                                            merge
+                                              { Empty = ""
+                                              , NonEmpty = λ(_ : Text) → _
+                                              }
+                                              ( List/fold
+                                                  Text
+                                                  installVars.linkDirs
+                                                  < Empty | NonEmpty : Text >
+                                                  ( λ(_ : Text) →
+                                                    λ ( _
+                                                      : < Empty
+                                                        | NonEmpty : Text
+                                                        >
+                                                      ) →
+                                                      merge
+                                                        { Empty =
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              _@1
+                                                        , NonEmpty =
+                                                            λ(_ : Text) →
+                                                              < Empty
+                                                              | NonEmpty : Text
+                                                              >.NonEmpty
+                                                                "${_@2}:${_}"
+                                                        }
+                                                        _
+                                                  )
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.Empty
+                                              )
+                                        , var = "LD_LIBRARY_PATH"
+                                        }
+                                ).value
+                            , var = "CMAKE_LIBRARY_PATH"
+                            }
+                          ]
+                        # ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    installVars.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             installVars.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                      )
+                  , procDir = Some "build"
+                  , program = "cmake"
+                  }
+              ]
+            # List/fold
+                Text
+                bins
+                ( List
+                    < Call :
+                        { arguments : List Text
+                        , environment :
+                            Optional (List { value : Text, var : Text })
+                        , procDir : Optional Text
+                        , program : Text
+                        }
+                    | CopyFile : { dest : Text, src : Text }
+                    | CreateDirectory : { dir : Text }
+                    | MakeExecutable : { file : Text }
+                    | Patch : { patchContents : Text }
+                    | Symlink : { linkName : Text, tgt : Text }
+                    | SymlinkBinary : { file : Text }
+                    | SymlinkManpage : { file : Text, section : Natural }
+                    | Write : { contents : Text, file : Text }
+                    >
+                )
+                ( λ(_ : Text) →
+                  λ ( _
+                    : List
+                        < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >
+                    ) →
+                      [ < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >.SymlinkBinary
+                          { file = _@1 }
+                      ]
+                    # _
+                )
+                ( [] : List
+                         < Call :
+                             { arguments : List Text
+                             , environment :
+                                 Optional (List { value : Text, var : Text })
+                             , procDir : Optional Text
+                             , program : Text
+                             }
+                         | CopyFile : { dest : Text, src : Text }
+                         | CreateDirectory : { dir : Text }
+                         | MakeExecutable : { file : Text }
+                         | Patch : { patchContents : Text }
+                         | Symlink : { linkName : Text, tgt : Text }
+                         | SymlinkBinary : { file : Text }
+                         | SymlinkManpage : { file : Text, section : Natural }
+                         | Write : { contents : Text, file : Text }
+                         >
+                )
+      , cmakePackage =
+        { buildCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                    [ "--build"
+                    , "."
+                    , "--config"
+                    , "Release"
+                    , "--"
+                    , "-j"
+                    , Natural/show cfg.cpus
+                    ]
+                  , environment = Some
+                      (   [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.includeDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "CMAKE_INCLUDE_PATH"
+                            }
+                          , { value =
+                                ( if    cfg.static
+                                  then  { value =
+                                            "${List/fold
+                                                 Text
+                                                 cfg.linkDirs
+                                                 Text
+                                                 ( λ(_ : Text) →
+                                                   λ(_ : Text) →
+                                                     "${_@1}:${_}"
+                                                 )
+                                                 ""}/usr/local/lib:/lib:/usr/lib"
+                                        , var = "LIBRARY_PATH"
+                                        }
+                                  else  { value =
+                                            merge
+                                              { Empty = ""
+                                              , NonEmpty = λ(_ : Text) → _
+                                              }
+                                              ( List/fold
+                                                  Text
+                                                  cfg.linkDirs
+                                                  < Empty | NonEmpty : Text >
+                                                  ( λ(_ : Text) →
+                                                    λ ( _
+                                                      : < Empty
+                                                        | NonEmpty : Text
+                                                        >
+                                                      ) →
+                                                      merge
+                                                        { Empty =
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              _@1
+                                                        , NonEmpty =
+                                                            λ(_ : Text) →
+                                                              < Empty
+                                                              | NonEmpty : Text
+                                                              >.NonEmpty
+                                                                "${_@2}:${_}"
+                                                        }
+                                                        _
+                                                  )
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.Empty
+                                              )
+                                        , var = "LD_LIBRARY_PATH"
+                                        }
+                                ).value
+                            , var = "CMAKE_LIBRARY_PATH"
+                            }
+                          ]
+                        # ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                      )
+                  , procDir = Some "build"
+                  , program = "cmake"
+                  }
+              ]
+        , configureCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.CreateDirectory
+                  { dir = "build" }
+              , < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                        [ "../"
+                        , "-DCMAKE_INSTALL_PREFIX:PATH=${cfg.installDir}"
+                        , "-DCMAKE_MAKE_PROGRAM=${merge
+                                                    { AIX = "make"
+                                                    , Android = "make"
+                                                    , Darwin = "make"
+                                                    , Dragonfly = "gmake"
+                                                    , FreeBSD = "gmake"
+                                                    , Haiku = "make"
+                                                    , Hurd = "make"
+                                                    , IOS = "make"
+                                                    , Linux = "make"
+                                                    , NetBSD = "gmake"
+                                                    , NoOs = "make"
+                                                    , OpenBSD = "gmake"
+                                                    , Redox = "make"
+                                                    , Solaris = "gmake"
+                                                    , Windows = "make"
+                                                    }
+                                                    cfg.buildOS}"
+                        ]
+                      # merge
+                          { None =
+                            [ "-DCMAKE_C_COMPILER=gcc"
+                            , "-DCMAKE_CXX_COMPILER=g++"
+                            ]
+                          , Some =
+                              λ ( tgt
+                                : { abi :
+                                      Optional
+                                        < GNU
+                                        | GNUabi64
+                                        | GNUeabi
+                                        | GNUeabihf
+                                        | GNUspe
+                                        | MinGw
+                                        >
+                                  , arch :
+                                      < AArch
+                                      | Alpha
+                                      | Arm
+                                      | HPPA
+                                      | HPPA64
+                                      | M68k
+                                      | Mips
+                                      | Mips64
+                                      | Mips64El
+                                      | MipsEl
+                                      | MipsIsa32r6
+                                      | MipsIsa32r6El
+                                      | MipsIsa64r6
+                                      | MipsIsa64r6El
+                                      | PowerPC
+                                      | PowerPC64
+                                      | PowerPC64le
+                                      | RISCV64
+                                      | S390x
+                                      | SH4
+                                      | Sparc64
+                                      | X64
+                                      | X86
+                                      >
+                                  , manufacturer :
+                                      Optional < Apple | IBM | PC | Unknown >
+                                  , os :
+                                      < AIX
+                                      | Android
+                                      | Darwin
+                                      | Dragonfly
+                                      | FreeBSD
+                                      | Haiku
+                                      | Hurd
+                                      | IOS
+                                      | Linux
+                                      | NetBSD
+                                      | NoOs
+                                      | OpenBSD
+                                      | Redox
+                                      | Solaris
+                                      | Windows
+                                      >
+                                  }
+                                ) →
+                                [ "-DCMAKE_C_COMPILER=${merge
+                                                          { AArch = "aarch64"
+                                                          , Alpha = "alpha"
+                                                          , Arm = "arm"
+                                                          , HPPA = "hppa"
+                                                          , HPPA64 = "hppa64"
+                                                          , M68k = "m68k"
+                                                          , Mips = "mips"
+                                                          , Mips64 = "mips64"
+                                                          , Mips64El =
+                                                              "mips64el"
+                                                          , MipsEl = "mipsel"
+                                                          , MipsIsa32r6 =
+                                                              "mipsisa32r6"
+                                                          , MipsIsa32r6El =
+                                                              "mipsisa32r6el"
+                                                          , MipsIsa64r6 =
+                                                              "mipsisa64r6"
+                                                          , MipsIsa64r6El =
+                                                              "mipsisa64r6el"
+                                                          , PowerPC = "powerpc"
+                                                          , PowerPC64 =
+                                                              "powerpc64"
+                                                          , PowerPC64le =
+                                                              "powerpc64le"
+                                                          , RISCV64 = "riscv64"
+                                                          , S390x = "s390x"
+                                                          , SH4 = "sh4"
+                                                          , Sparc64 = "sparc64"
+                                                          , X64 = "x86_64"
+                                                          , X86 = "i686"
+                                                          }
+                                                          tgt.arch}-${merge
+                                                                        { AIX =
+                                                                            "aix"
+                                                                        , Android =
+                                                                            "android"
+                                                                        , Darwin =
+                                                                            "darwin"
+                                                                        , Dragonfly =
+                                                                            "dragonfly"
+                                                                        , FreeBSD =
+                                                                            "freebsd"
+                                                                        , Haiku =
+                                                                            "haiku"
+                                                                        , Hurd =
+                                                                            "hurd"
+                                                                        , IOS =
+                                                                            "darwin"
+                                                                        , Linux =
+                                                                            "linux"
+                                                                        , NetBSD =
+                                                                            "netbsd"
+                                                                        , NoOs =
+                                                                            "none"
+                                                                        , OpenBSD =
+                                                                            "openbsd"
+                                                                        , Redox =
+                                                                            "redox"
+                                                                        , Solaris =
+                                                                            "solaris"
+                                                                        , Windows =
+                                                                            "w64"
+                                                                        }
+                                                                        tgt.os}${merge
+                                                                                   { None =
+                                                                                       ""
+                                                                                   , Some =
+                                                                                       λ ( abi
+                                                                                         : < GNU
+                                                                                           | GNUabi64
+                                                                                           | GNUeabi
+                                                                                           | GNUeabihf
+                                                                                           | GNUspe
+                                                                                           | MinGw
+                                                                                           >
+                                                                                         ) →
+                                                                                         "-${merge
+                                                                                               { GNU =
+                                                                                                   "gnu"
+                                                                                               , GNUabi64 =
+                                                                                                   "gnuabi64"
+                                                                                               , GNUeabi =
+                                                                                                   "gnueabi"
+                                                                                               , GNUeabihf =
+                                                                                                   "gnueabihf"
+                                                                                               , GNUspe =
+                                                                                                   "gnuspe"
+                                                                                               , MinGw =
+                                                                                                   "mingw32"
+                                                                                               }
+                                                                                               abi}"
+                                                                                   }
+                                                                                   tgt.abi}-gcc"
+                                , "-DCMAKE_CXX_COMPILER=${merge
+                                                            { AArch = "aarch64"
+                                                            , Alpha = "alpha"
+                                                            , Arm = "arm"
+                                                            , HPPA = "hppa"
+                                                            , HPPA64 = "hppa64"
+                                                            , M68k = "m68k"
+                                                            , Mips = "mips"
+                                                            , Mips64 = "mips64"
+                                                            , Mips64El =
+                                                                "mips64el"
+                                                            , MipsEl = "mipsel"
+                                                            , MipsIsa32r6 =
+                                                                "mipsisa32r6"
+                                                            , MipsIsa32r6El =
+                                                                "mipsisa32r6el"
+                                                            , MipsIsa64r6 =
+                                                                "mipsisa64r6"
+                                                            , MipsIsa64r6El =
+                                                                "mipsisa64r6el"
+                                                            , PowerPC =
+                                                                "powerpc"
+                                                            , PowerPC64 =
+                                                                "powerpc64"
+                                                            , PowerPC64le =
+                                                                "powerpc64le"
+                                                            , RISCV64 =
+                                                                "riscv64"
+                                                            , S390x = "s390x"
+                                                            , SH4 = "sh4"
+                                                            , Sparc64 =
+                                                                "sparc64"
+                                                            , X64 = "x86_64"
+                                                            , X86 = "i686"
+                                                            }
+                                                            tgt.arch}-${merge
+                                                                          { AIX =
+                                                                              "aix"
+                                                                          , Android =
+                                                                              "android"
+                                                                          , Darwin =
+                                                                              "darwin"
+                                                                          , Dragonfly =
+                                                                              "dragonfly"
+                                                                          , FreeBSD =
+                                                                              "freebsd"
+                                                                          , Haiku =
+                                                                              "haiku"
+                                                                          , Hurd =
+                                                                              "hurd"
+                                                                          , IOS =
+                                                                              "darwin"
+                                                                          , Linux =
+                                                                              "linux"
+                                                                          , NetBSD =
+                                                                              "netbsd"
+                                                                          , NoOs =
+                                                                              "none"
+                                                                          , OpenBSD =
+                                                                              "openbsd"
+                                                                          , Redox =
+                                                                              "redox"
+                                                                          , Solaris =
+                                                                              "solaris"
+                                                                          , Windows =
+                                                                              "w64"
+                                                                          }
+                                                                          tgt.os}${merge
+                                                                                     { None =
+                                                                                         ""
+                                                                                     , Some =
+                                                                                         λ ( abi
+                                                                                           : < GNU
+                                                                                             | GNUabi64
+                                                                                             | GNUeabi
+                                                                                             | GNUeabihf
+                                                                                             | GNUspe
+                                                                                             | MinGw
+                                                                                             >
+                                                                                           ) →
+                                                                                           "-${merge
+                                                                                                 { GNU =
+                                                                                                     "gnu"
+                                                                                                 , GNUabi64 =
+                                                                                                     "gnuabi64"
+                                                                                                 , GNUeabi =
+                                                                                                     "gnueabi"
+                                                                                                 , GNUeabihf =
+                                                                                                     "gnueabihf"
+                                                                                                 , GNUspe =
+                                                                                                     "gnuspe"
+                                                                                                 , MinGw =
+                                                                                                     "mingw32"
+                                                                                                 }
+                                                                                                 abi}"
+                                                                                     }
+                                                                                     tgt.abi}-g++"
+                                ]
+                          }
+                          cfg.targetTriple
+                      # merge
+                          { None = [] : List Text
+                          , Some =
+                              λ ( tgt
+                                : { abi :
+                                      Optional
+                                        < GNU
+                                        | GNUabi64
+                                        | GNUeabi
+                                        | GNUeabihf
+                                        | GNUspe
+                                        | MinGw
+                                        >
+                                  , arch :
+                                      < AArch
+                                      | Alpha
+                                      | Arm
+                                      | HPPA
+                                      | HPPA64
+                                      | M68k
+                                      | Mips
+                                      | Mips64
+                                      | Mips64El
+                                      | MipsEl
+                                      | MipsIsa32r6
+                                      | MipsIsa32r6El
+                                      | MipsIsa64r6
+                                      | MipsIsa64r6El
+                                      | PowerPC
+                                      | PowerPC64
+                                      | PowerPC64le
+                                      | RISCV64
+                                      | S390x
+                                      | SH4
+                                      | Sparc64
+                                      | X64
+                                      | X86
+                                      >
+                                  , manufacturer :
+                                      Optional < Apple | IBM | PC | Unknown >
+                                  , os :
+                                      < AIX
+                                      | Android
+                                      | Darwin
+                                      | Dragonfly
+                                      | FreeBSD
+                                      | Haiku
+                                      | Hurd
+                                      | IOS
+                                      | Linux
+                                      | NetBSD
+                                      | NoOs
+                                      | OpenBSD
+                                      | Redox
+                                      | Solaris
+                                      | Windows
+                                      >
+                                  }
+                                ) →
+                                [ "-DCMAKE_SYSTEM_NAME=${merge
+                                                           { AIX = "AIX"
+                                                           , Android = "Android"
+                                                           , Darwin = "Darwin"
+                                                           , Dragonfly = "BSD"
+                                                           , FreeBSD = "BSD"
+                                                           , Haiku = "Haiku"
+                                                           , Hurd = "Hurd"
+                                                           , IOS = "Darwin"
+                                                           , Linux = "Linux"
+                                                           , NetBSD = "BSD"
+                                                           , NoOs = "Generic"
+                                                           , OpenBSD = "BSD"
+                                                           , Redox = "Redox"
+                                                           , Solaris = "Solaris"
+                                                           , Windows = "Windows"
+                                                           }
+                                                           tgt.os}"
+                                ]
+                          }
+                          cfg.targetTriple
+                  , environment = Some
+                      (   [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.includeDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "CMAKE_INCLUDE_PATH"
+                            }
+                          , { value =
+                                ( if    cfg.static
+                                  then  { value =
+                                            "${List/fold
+                                                 Text
+                                                 cfg.linkDirs
+                                                 Text
+                                                 ( λ(_ : Text) →
+                                                   λ(_ : Text) →
+                                                     "${_@1}:${_}"
+                                                 )
+                                                 ""}/usr/local/lib:/lib:/usr/lib"
+                                        , var = "LIBRARY_PATH"
+                                        }
+                                  else  { value =
+                                            merge
+                                              { Empty = ""
+                                              , NonEmpty = λ(_ : Text) → _
+                                              }
+                                              ( List/fold
+                                                  Text
+                                                  cfg.linkDirs
+                                                  < Empty | NonEmpty : Text >
+                                                  ( λ(_ : Text) →
+                                                    λ ( _
+                                                      : < Empty
+                                                        | NonEmpty : Text
+                                                        >
+                                                      ) →
+                                                      merge
+                                                        { Empty =
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              _@1
+                                                        , NonEmpty =
+                                                            λ(_ : Text) →
+                                                              < Empty
+                                                              | NonEmpty : Text
+                                                              >.NonEmpty
+                                                                "${_@2}:${_}"
+                                                        }
+                                                        _
+                                                  )
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.Empty
+                                              )
+                                        , var = "LD_LIBRARY_PATH"
+                                        }
+                                ).value
+                            , var = "CMAKE_LIBRARY_PATH"
+                            }
+                          ]
+                        # ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                      )
+                  , procDir = Some "build"
+                  , program = "cmake"
+                  }
+              ]
+        , installCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                    [ "--build"
+                    , "."
+                    , "--target"
+                    , "install"
+                    , "--config"
+                    , "Release"
+                    ]
+                  , environment = Some
+                      (   [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.includeDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "CMAKE_INCLUDE_PATH"
+                            }
+                          , { value =
+                                ( if    cfg.static
+                                  then  { value =
+                                            "${List/fold
+                                                 Text
+                                                 cfg.linkDirs
+                                                 Text
+                                                 ( λ(_ : Text) →
+                                                   λ(_ : Text) →
+                                                     "${_@1}:${_}"
+                                                 )
+                                                 ""}/usr/local/lib:/lib:/usr/lib"
+                                        , var = "LIBRARY_PATH"
+                                        }
+                                  else  { value =
+                                            merge
+                                              { Empty = ""
+                                              , NonEmpty = λ(_ : Text) → _
+                                              }
+                                              ( List/fold
+                                                  Text
+                                                  cfg.linkDirs
+                                                  < Empty | NonEmpty : Text >
+                                                  ( λ(_ : Text) →
+                                                    λ ( _
+                                                      : < Empty
+                                                        | NonEmpty : Text
+                                                        >
+                                                      ) →
+                                                      merge
+                                                        { Empty =
+                                                            < Empty
+                                                            | NonEmpty : Text
+                                                            >.NonEmpty
+                                                              _@1
+                                                        , NonEmpty =
+                                                            λ(_ : Text) →
+                                                              < Empty
+                                                              | NonEmpty : Text
+                                                              >.NonEmpty
+                                                                "${_@2}:${_}"
+                                                        }
+                                                        _
+                                                  )
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.Empty
+                                              )
+                                        , var = "LD_LIBRARY_PATH"
+                                        }
+                                ).value
+                            , var = "CMAKE_LIBRARY_PATH"
+                            }
+                          ]
+                        # ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                      )
+                  , procDir = Some "build"
+                  , program = "cmake"
+                  }
+              ]
+        , pkgBuildDeps =
+          [ { bound =
+                < Lower : { lower : List Natural }
+                | LowerUpper : { lower : List Natural, upper : List Natural }
+                | NoBound
+                | Upper : { upper : List Natural }
+                >.NoBound
+            , name = "cmake"
+            }
+          ]
+        , pkgDeps =
+            [] : List
+                   { bound :
+                       < Lower : { lower : List Natural }
+                       | LowerUpper :
+                           { lower : List Natural, upper : List Natural }
+                       | NoBound
+                       | Upper : { upper : List Natural }
+                       >
+                   , name : Text
+                   }
+        }
+      , cmakeSome =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            Some
+              (   [ { value =
+                        merge
+                          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                          ( List/fold
+                              Text
+                              (cfg.shareDirs # cfg.linkDirs)
+                              < Empty | NonEmpty : Text >
+                              ( λ(_ : Text) →
+                                λ(_ : < Empty | NonEmpty : Text >) →
+                                  merge
+                                    { Empty =
+                                        < Empty | NonEmpty : Text >.NonEmpty
+                                          "${_@1}/pkgconfig"
+                                    , NonEmpty =
+                                        λ(_ : Text) →
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            "${_@2}/pkgconfig:${_}"
+                                    }
+                                    _
+                              )
+                              < Empty | NonEmpty : Text >.Empty
+                          )
+                    , var = "PKG_CONFIG_PATH"
+                    }
+                  , { value =
+                        merge
+                          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                          ( List/fold
+                              Text
+                              cfg.includeDirs
+                              < Empty | NonEmpty : Text >
+                              ( λ(_ : Text) →
+                                λ(_ : < Empty | NonEmpty : Text >) →
+                                  merge
+                                    { Empty =
+                                        < Empty | NonEmpty : Text >.NonEmpty _@1
+                                    , NonEmpty =
+                                        λ(_ : Text) →
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            "${_@2}:${_}"
+                                    }
+                                    _
+                              )
+                              < Empty | NonEmpty : Text >.Empty
+                          )
+                    , var = "CMAKE_INCLUDE_PATH"
+                    }
+                  , { value =
+                        ( if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        ).value
+                    , var = "CMAKE_LIBRARY_PATH"
+                    }
+                  ]
+                # ( if    merge
+                            { AIX = True
+                            , Android = True
+                            , Darwin = True
+                            , Dragonfly = True
+                            , FreeBSD = True
+                            , Haiku = False
+                            , Hurd = True
+                            , IOS = True
+                            , Linux = True
+                            , NetBSD = True
+                            , NoOs = False
+                            , OpenBSD = True
+                            , Redox = False
+                            , Solaris = True
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  [ { value =
+                                "${List/fold
+                                     Text
+                                     cfg.binDirs
+                                     Text
+                                     (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                     ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                            , var = "PATH"
+                            }
+                          ]
+                    else  [] : List { value : Text, var : Text }
+                  )
+              )
+      , configEnv =
+          λ(linkLibs : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              ( if    merge
+                        { AIX = True
+                        , Android = True
+                        , Darwin = True
+                        , Dragonfly = True
+                        , FreeBSD = True
+                        , Haiku = False
+                        , Hurd = True
+                        , IOS = True
+                        , Linux = True
+                        , NetBSD = True
+                        , NoOs = False
+                        , OpenBSD = True
+                        , Redox = False
+                        , Solaris = True
+                        , Windows = False
+                        }
+                        cfg.buildOS
+                then  [ { value =
+                            "${List/fold
+                                 Text
+                                 cfg.binDirs
+                                 Text
+                                 (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                 ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                        , var = "PATH"
+                        }
+                      ]
+                else  [] : List { value : Text, var : Text }
+              )
+            # [ { value =
+                    "${merge
+                         { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                         ( List/fold
+                             Text
+                             cfg.linkDirs
+                             < Empty | NonEmpty : Text >
+                             ( λ(_ : Text) →
+                               λ(_ : < Empty | NonEmpty : Text >) →
+                                 merge
+                                   { Empty =
+                                       < Empty | NonEmpty : Text >.NonEmpty
+                                         "-L${_@1}"
+                                   , NonEmpty =
+                                       λ(_ : Text) →
+                                         < Empty | NonEmpty : Text >.NonEmpty
+                                           "-L${_@2} ${_}"
+                                   }
+                                   _
+                             )
+                             < Empty | NonEmpty : Text >.Empty
+                         )}${List/fold
+                               Text
+                               linkLibs
+                               Text
+                               (λ(_ : Text) → λ(_ : Text) → " -l${_@1}${_}")
+                               ""}${List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      Text
+                                      ( λ(_ : Text) →
+                                        λ(_ : Text) →
+                                          "${if    merge
+                                                     { AIX = False
+                                                     , Android = False
+                                                     , Darwin = True
+                                                     , Dragonfly = False
+                                                     , FreeBSD = False
+                                                     , Haiku = False
+                                                     , Hurd = False
+                                                     , IOS = False
+                                                     , Linux = False
+                                                     , NetBSD = False
+                                                     , NoOs = False
+                                                     , OpenBSD = False
+                                                     , Redox = False
+                                                     , Solaris = False
+                                                     , Windows = False
+                                                     }
+                                                     cfg.buildOS
+                                             then  ""
+                                             else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                      )
+                                      ""}"
+                , var = "LDFLAGS"
+                }
+              , { value =
+                    "${merge
+                         { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                         ( List/fold
+                             Text
+                             cfg.includeDirs
+                             < Empty | NonEmpty : Text >
+                             ( λ(_ : Text) →
+                               λ(_ : < Empty | NonEmpty : Text >) →
+                                 merge
+                                   { Empty =
+                                       < Empty | NonEmpty : Text >.NonEmpty
+                                         "-I${_@1}"
+                                   , NonEmpty =
+                                       λ(_ : Text) →
+                                         < Empty | NonEmpty : Text >.NonEmpty
+                                           "-I${_@2} ${_}"
+                                   }
+                                   _
+                             )
+                             < Empty | NonEmpty : Text >.Empty
+                         )}${if cfg.static then " -static" else ""}"
+                , var = "CPPFLAGS"
+                }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          (cfg.shareDirs # cfg.linkDirs)
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty
+                                      "${_@1}/pkgconfig"
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}/pkgconfig:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "PKG_CONFIG_PATH"
+                }
+              , if    cfg.static
+                then  { value =
+                          "${List/fold
+                               Text
+                               cfg.linkDirs
+                               Text
+                               (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                               ""}/usr/local/lib:/lib:/usr/lib"
+                      , var = "LIBRARY_PATH"
+                      }
+                else  { value =
+                          merge
+                            { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                            ( List/fold
+                                Text
+                                cfg.linkDirs
+                                < Empty | NonEmpty : Text >
+                                ( λ(_ : Text) →
+                                  λ(_ : < Empty | NonEmpty : Text >) →
+                                    merge
+                                      { Empty =
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            _@1
+                                      , NonEmpty =
+                                          λ(_ : Text) →
+                                            < Empty | NonEmpty : Text >.NonEmpty
+                                              "${_@2}:${_}"
+                                      }
+                                      _
+                                )
+                                < Empty | NonEmpty : Text >.Empty
+                            )
+                      , var = "LD_LIBRARY_PATH"
+                      }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          cfg.linkDirs
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty _@1
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "LD_RUN_PATH"
+                }
+              , { value =
+                    merge
+                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                      ( List/fold
+                          Text
+                          cfg.linkDirs
+                          < Empty | NonEmpty : Text >
+                          ( λ(_ : Text) →
+                            λ(_ : < Empty | NonEmpty : Text >) →
+                              merge
+                                { Empty =
+                                    < Empty | NonEmpty : Text >.NonEmpty
+                                      "${_@1}/site_perl/5.30.2/${merge
+                                                                   { AArch =
+                                                                       "aarch64"
+                                                                   , Alpha =
+                                                                       "alpha"
+                                                                   , Arm = "arm"
+                                                                   , HPPA =
+                                                                       "hppa"
+                                                                   , HPPA64 =
+                                                                       "hppa64"
+                                                                   , M68k =
+                                                                       "m68k"
+                                                                   , Mips =
+                                                                       "mips"
+                                                                   , Mips64 =
+                                                                       "mips64"
+                                                                   , Mips64El =
+                                                                       "mips64el"
+                                                                   , MipsEl =
+                                                                       "mipsel"
+                                                                   , MipsIsa32r6 =
+                                                                       "mipsisa32r6"
+                                                                   , MipsIsa32r6El =
+                                                                       "mipsisa32r6el"
+                                                                   , MipsIsa64r6 =
+                                                                       "mipsisa64r6"
+                                                                   , MipsIsa64r6El =
+                                                                       "mipsisa64r6el"
+                                                                   , PowerPC =
+                                                                       "powerpc"
+                                                                   , PowerPC64 =
+                                                                       "powerpc64"
+                                                                   , PowerPC64le =
+                                                                       "powerpc64le"
+                                                                   , RISCV64 =
+                                                                       "riscv64"
+                                                                   , S390x =
+                                                                       "s390x"
+                                                                   , SH4 = "sh4"
+                                                                   , Sparc64 =
+                                                                       "sparc64"
+                                                                   , X64 =
+                                                                       "x86_64"
+                                                                   , X86 =
+                                                                       "i686"
+                                                                   }
+                                                                   cfg.buildArch}-${merge
+                                                                                      { AIX =
+                                                                                          "aix"
+                                                                                      , Android =
+                                                                                          "android"
+                                                                                      , Darwin =
+                                                                                          "darwin"
+                                                                                      , Dragonfly =
+                                                                                          "dragonfly"
+                                                                                      , FreeBSD =
+                                                                                          "freebsd"
+                                                                                      , Haiku =
+                                                                                          "haiku"
+                                                                                      , Hurd =
+                                                                                          "hurd"
+                                                                                      , IOS =
+                                                                                          "darwin"
+                                                                                      , Linux =
+                                                                                          "linux"
+                                                                                      , NetBSD =
+                                                                                          "netbsd"
+                                                                                      , NoOs =
+                                                                                          "none"
+                                                                                      , OpenBSD =
+                                                                                          "openbsd"
+                                                                                      , Redox =
+                                                                                          "redox"
+                                                                                      , Solaris =
+                                                                                          "solaris"
+                                                                                      , Windows =
+                                                                                          "w64"
+                                                                                      }
+                                                                                      cfg.buildOS}/"
+                                , NonEmpty =
+                                    λ(_ : Text) →
+                                      < Empty | NonEmpty : Text >.NonEmpty
+                                        "${_@2}/site_perl/5.30.2/${merge
+                                                                     { AArch =
+                                                                         "aarch64"
+                                                                     , Alpha =
+                                                                         "alpha"
+                                                                     , Arm =
+                                                                         "arm"
+                                                                     , HPPA =
+                                                                         "hppa"
+                                                                     , HPPA64 =
+                                                                         "hppa64"
+                                                                     , M68k =
+                                                                         "m68k"
+                                                                     , Mips =
+                                                                         "mips"
+                                                                     , Mips64 =
+                                                                         "mips64"
+                                                                     , Mips64El =
+                                                                         "mips64el"
+                                                                     , MipsEl =
+                                                                         "mipsel"
+                                                                     , MipsIsa32r6 =
+                                                                         "mipsisa32r6"
+                                                                     , MipsIsa32r6El =
+                                                                         "mipsisa32r6el"
+                                                                     , MipsIsa64r6 =
+                                                                         "mipsisa64r6"
+                                                                     , MipsIsa64r6El =
+                                                                         "mipsisa64r6el"
+                                                                     , PowerPC =
+                                                                         "powerpc"
+                                                                     , PowerPC64 =
+                                                                         "powerpc64"
+                                                                     , PowerPC64le =
+                                                                         "powerpc64le"
+                                                                     , RISCV64 =
+                                                                         "riscv64"
+                                                                     , S390x =
+                                                                         "s390x"
+                                                                     , SH4 =
+                                                                         "sh4"
+                                                                     , Sparc64 =
+                                                                         "sparc64"
+                                                                     , X64 =
+                                                                         "x86_64"
+                                                                     , X86 =
+                                                                         "i686"
+                                                                     }
+                                                                     cfg.buildArch}-${merge
+                                                                                        { AIX =
+                                                                                            "aix"
+                                                                                        , Android =
+                                                                                            "android"
+                                                                                        , Darwin =
+                                                                                            "darwin"
+                                                                                        , Dragonfly =
+                                                                                            "dragonfly"
+                                                                                        , FreeBSD =
+                                                                                            "freebsd"
+                                                                                        , Haiku =
+                                                                                            "haiku"
+                                                                                        , Hurd =
+                                                                                            "hurd"
+                                                                                        , IOS =
+                                                                                            "darwin"
+                                                                                        , Linux =
+                                                                                            "linux"
+                                                                                        , NetBSD =
+                                                                                            "netbsd"
+                                                                                        , NoOs =
+                                                                                            "none"
+                                                                                        , OpenBSD =
+                                                                                            "openbsd"
+                                                                                        , Redox =
+                                                                                            "redox"
+                                                                                        , Solaris =
+                                                                                            "solaris"
+                                                                                        , Windows =
+                                                                                            "w64"
+                                                                                        }
+                                                                                        cfg.buildOS}/:${_}"
+                                }
+                                _
+                          )
+                          < Empty | NonEmpty : Text >.Empty
+                      )
+                , var = "PERL5LIB"
+                }
+              ]
+      , configSome =
+          λ(linkLibs : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            Some
+              (   ( if    merge
+                            { AIX = True
+                            , Android = True
+                            , Darwin = True
+                            , Dragonfly = True
+                            , FreeBSD = True
+                            , Haiku = False
+                            , Hurd = True
+                            , IOS = True
+                            , Linux = True
+                            , NetBSD = True
+                            , NoOs = False
+                            , OpenBSD = True
+                            , Redox = False
+                            , Solaris = True
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  [ { value =
+                                "${List/fold
+                                     Text
+                                     cfg.binDirs
+                                     Text
+                                     (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                     ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                            , var = "PATH"
+                            }
+                          ]
+                    else  [] : List { value : Text, var : Text }
+                  )
+                # [ { value =
+                        "${merge
+                             { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                             ( List/fold
+                                 Text
+                                 cfg.linkDirs
+                                 < Empty | NonEmpty : Text >
+                                 ( λ(_ : Text) →
+                                   λ(_ : < Empty | NonEmpty : Text >) →
+                                     merge
+                                       { Empty =
+                                           < Empty | NonEmpty : Text >.NonEmpty
+                                             "-L${_@1}"
+                                       , NonEmpty =
+                                           λ(_ : Text) →
+                                             < Empty
+                                             | NonEmpty : Text
+                                             >.NonEmpty
+                                               "-L${_@2} ${_}"
+                                       }
+                                       _
+                                 )
+                                 < Empty | NonEmpty : Text >.Empty
+                             )}${List/fold
+                                   Text
+                                   linkLibs
+                                   Text
+                                   (λ(_ : Text) → λ(_ : Text) → " -l${_@1}${_}")
+                                   ""}${List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          Text
+                                          ( λ(_ : Text) →
+                                            λ(_ : Text) →
+                                              "${if    merge
+                                                         { AIX = False
+                                                         , Android = False
+                                                         , Darwin = True
+                                                         , Dragonfly = False
+                                                         , FreeBSD = False
+                                                         , Haiku = False
+                                                         , Hurd = False
+                                                         , IOS = False
+                                                         , Linux = False
+                                                         , NetBSD = False
+                                                         , NoOs = False
+                                                         , OpenBSD = False
+                                                         , Redox = False
+                                                         , Solaris = False
+                                                         , Windows = False
+                                                         }
+                                                         cfg.buildOS
+                                                 then  ""
+                                                 else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                          )
+                                          ""}"
+                    , var = "LDFLAGS"
+                    }
+                  , { value =
+                        "${merge
+                             { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                             ( List/fold
+                                 Text
+                                 cfg.includeDirs
+                                 < Empty | NonEmpty : Text >
+                                 ( λ(_ : Text) →
+                                   λ(_ : < Empty | NonEmpty : Text >) →
+                                     merge
+                                       { Empty =
+                                           < Empty | NonEmpty : Text >.NonEmpty
+                                             "-I${_@1}"
+                                       , NonEmpty =
+                                           λ(_ : Text) →
+                                             < Empty
+                                             | NonEmpty : Text
+                                             >.NonEmpty
+                                               "-I${_@2} ${_}"
+                                       }
+                                       _
+                                 )
+                                 < Empty | NonEmpty : Text >.Empty
+                             )}${if cfg.static then " -static" else ""}"
+                    , var = "CPPFLAGS"
+                    }
+                  , { value =
+                        merge
+                          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                          ( List/fold
+                              Text
+                              (cfg.shareDirs # cfg.linkDirs)
+                              < Empty | NonEmpty : Text >
+                              ( λ(_ : Text) →
+                                λ(_ : < Empty | NonEmpty : Text >) →
+                                  merge
+                                    { Empty =
+                                        < Empty | NonEmpty : Text >.NonEmpty
+                                          "${_@1}/pkgconfig"
+                                    , NonEmpty =
+                                        λ(_ : Text) →
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            "${_@2}/pkgconfig:${_}"
+                                    }
+                                    _
+                              )
+                              < Empty | NonEmpty : Text >.Empty
+                          )
+                    , var = "PKG_CONFIG_PATH"
+                    }
+                  , if    cfg.static
+                    then  { value =
+                              "${List/fold
+                                   Text
+                                   cfg.linkDirs
+                                   Text
+                                   (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                                   ""}/usr/local/lib:/lib:/usr/lib"
+                          , var = "LIBRARY_PATH"
+                          }
+                    else  { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_LIBRARY_PATH"
+                          }
+                  , { value =
+                        merge
+                          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                          ( List/fold
+                              Text
+                              cfg.linkDirs
+                              < Empty | NonEmpty : Text >
+                              ( λ(_ : Text) →
+                                λ(_ : < Empty | NonEmpty : Text >) →
+                                  merge
+                                    { Empty =
+                                        < Empty | NonEmpty : Text >.NonEmpty _@1
+                                    , NonEmpty =
+                                        λ(_ : Text) →
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            "${_@2}:${_}"
+                                    }
+                                    _
+                              )
+                              < Empty | NonEmpty : Text >.Empty
+                          )
+                    , var = "LD_RUN_PATH"
+                    }
+                  , { value =
+                        merge
+                          { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                          ( List/fold
+                              Text
+                              cfg.linkDirs
+                              < Empty | NonEmpty : Text >
+                              ( λ(_ : Text) →
+                                λ(_ : < Empty | NonEmpty : Text >) →
+                                  merge
+                                    { Empty =
+                                        < Empty | NonEmpty : Text >.NonEmpty
+                                          "${_@1}/site_perl/5.30.2/${merge
+                                                                       { AArch =
+                                                                           "aarch64"
+                                                                       , Alpha =
+                                                                           "alpha"
+                                                                       , Arm =
+                                                                           "arm"
+                                                                       , HPPA =
+                                                                           "hppa"
+                                                                       , HPPA64 =
+                                                                           "hppa64"
+                                                                       , M68k =
+                                                                           "m68k"
+                                                                       , Mips =
+                                                                           "mips"
+                                                                       , Mips64 =
+                                                                           "mips64"
+                                                                       , Mips64El =
+                                                                           "mips64el"
+                                                                       , MipsEl =
+                                                                           "mipsel"
+                                                                       , MipsIsa32r6 =
+                                                                           "mipsisa32r6"
+                                                                       , MipsIsa32r6El =
+                                                                           "mipsisa32r6el"
+                                                                       , MipsIsa64r6 =
+                                                                           "mipsisa64r6"
+                                                                       , MipsIsa64r6El =
+                                                                           "mipsisa64r6el"
+                                                                       , PowerPC =
+                                                                           "powerpc"
+                                                                       , PowerPC64 =
+                                                                           "powerpc64"
+                                                                       , PowerPC64le =
+                                                                           "powerpc64le"
+                                                                       , RISCV64 =
+                                                                           "riscv64"
+                                                                       , S390x =
+                                                                           "s390x"
+                                                                       , SH4 =
+                                                                           "sh4"
+                                                                       , Sparc64 =
+                                                                           "sparc64"
+                                                                       , X64 =
+                                                                           "x86_64"
+                                                                       , X86 =
+                                                                           "i686"
+                                                                       }
+                                                                       cfg.buildArch}-${merge
+                                                                                          { AIX =
+                                                                                              "aix"
+                                                                                          , Android =
+                                                                                              "android"
+                                                                                          , Darwin =
+                                                                                              "darwin"
+                                                                                          , Dragonfly =
+                                                                                              "dragonfly"
+                                                                                          , FreeBSD =
+                                                                                              "freebsd"
+                                                                                          , Haiku =
+                                                                                              "haiku"
+                                                                                          , Hurd =
+                                                                                              "hurd"
+                                                                                          , IOS =
+                                                                                              "darwin"
+                                                                                          , Linux =
+                                                                                              "linux"
+                                                                                          , NetBSD =
+                                                                                              "netbsd"
+                                                                                          , NoOs =
+                                                                                              "none"
+                                                                                          , OpenBSD =
+                                                                                              "openbsd"
+                                                                                          , Redox =
+                                                                                              "redox"
+                                                                                          , Solaris =
+                                                                                              "solaris"
+                                                                                          , Windows =
+                                                                                              "w64"
+                                                                                          }
+                                                                                          cfg.buildOS}/"
+                                    , NonEmpty =
+                                        λ(_ : Text) →
+                                          < Empty | NonEmpty : Text >.NonEmpty
+                                            "${_@2}/site_perl/5.30.2/${merge
+                                                                         { AArch =
+                                                                             "aarch64"
+                                                                         , Alpha =
+                                                                             "alpha"
+                                                                         , Arm =
+                                                                             "arm"
+                                                                         , HPPA =
+                                                                             "hppa"
+                                                                         , HPPA64 =
+                                                                             "hppa64"
+                                                                         , M68k =
+                                                                             "m68k"
+                                                                         , Mips =
+                                                                             "mips"
+                                                                         , Mips64 =
+                                                                             "mips64"
+                                                                         , Mips64El =
+                                                                             "mips64el"
+                                                                         , MipsEl =
+                                                                             "mipsel"
+                                                                         , MipsIsa32r6 =
+                                                                             "mipsisa32r6"
+                                                                         , MipsIsa32r6El =
+                                                                             "mipsisa32r6el"
+                                                                         , MipsIsa64r6 =
+                                                                             "mipsisa64r6"
+                                                                         , MipsIsa64r6El =
+                                                                             "mipsisa64r6el"
+                                                                         , PowerPC =
+                                                                             "powerpc"
+                                                                         , PowerPC64 =
+                                                                             "powerpc64"
+                                                                         , PowerPC64le =
+                                                                             "powerpc64le"
+                                                                         , RISCV64 =
+                                                                             "riscv64"
+                                                                         , S390x =
+                                                                             "s390x"
+                                                                         , SH4 =
+                                                                             "sh4"
+                                                                         , Sparc64 =
+                                                                             "sparc64"
+                                                                         , X64 =
+                                                                             "x86_64"
+                                                                         , X86 =
+                                                                             "i686"
+                                                                         }
+                                                                         cfg.buildArch}-${merge
+                                                                                            { AIX =
+                                                                                                "aix"
+                                                                                            , Android =
+                                                                                                "android"
+                                                                                            , Darwin =
+                                                                                                "darwin"
+                                                                                            , Dragonfly =
+                                                                                                "dragonfly"
+                                                                                            , FreeBSD =
+                                                                                                "freebsd"
+                                                                                            , Haiku =
+                                                                                                "haiku"
+                                                                                            , Hurd =
+                                                                                                "hurd"
+                                                                                            , IOS =
+                                                                                                "darwin"
+                                                                                            , Linux =
+                                                                                                "linux"
+                                                                                            , NetBSD =
+                                                                                                "netbsd"
+                                                                                            , NoOs =
+                                                                                                "none"
+                                                                                            , OpenBSD =
+                                                                                                "openbsd"
+                                                                                            , Redox =
+                                                                                                "redox"
+                                                                                            , Solaris =
+                                                                                                "solaris"
+                                                                                            , Windows =
+                                                                                                "w64"
+                                                                                            }
+                                                                                            cfg.buildOS}/:${_}"
+                                    }
+                                    _
+                              )
+                              < Empty | NonEmpty : Text >.Empty
+                          )
+                    , var = "PERL5LIB"
+                    }
+                  ]
+              )
+      , configWithEnv =
+          λ ( envVars
+            : List Text →
+              { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              } →
+                Optional (List { value : Text, var : Text })
+            ) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      ( merge
+                          { None = [ "--prefix=${cfg.installDir}" ]
+                          , Some =
+                              λ(x : Text) → [ "--prefix=${cfg.installDir}", x ]
+                          }
+                          ( merge
+                              { None = None Text
+                              , Some =
+                                  λ ( _
+                                    : { abi :
+                                          Optional
+                                            < GNU
+                                            | GNUabi64
+                                            | GNUeabi
+                                            | GNUeabihf
+                                            | GNUspe
+                                            | MinGw
+                                            >
+                                      , arch :
+                                          < AArch
+                                          | Alpha
+                                          | Arm
+                                          | HPPA
+                                          | HPPA64
+                                          | M68k
+                                          | Mips
+                                          | Mips64
+                                          | Mips64El
+                                          | MipsEl
+                                          | MipsIsa32r6
+                                          | MipsIsa32r6El
+                                          | MipsIsa64r6
+                                          | MipsIsa64r6El
+                                          | PowerPC
+                                          | PowerPC64
+                                          | PowerPC64le
+                                          | RISCV64
+                                          | S390x
+                                          | SH4
+                                          | Sparc64
+                                          | X64
+                                          | X86
+                                          >
+                                      , manufacturer :
+                                          Optional
+                                            < Apple | IBM | PC | Unknown >
+                                      , os :
+                                          < AIX
+                                          | Android
+                                          | Darwin
+                                          | Dragonfly
+                                          | FreeBSD
+                                          | Haiku
+                                          | Hurd
+                                          | IOS
+                                          | Linux
+                                          | NetBSD
+                                          | NoOs
+                                          | OpenBSD
+                                          | Redox
+                                          | Solaris
+                                          | Windows
+                                          >
+                                      }
+                                    ) →
+                                    Some
+                                      "--host=${merge
+                                                  { AArch = "aarch64"
+                                                  , Alpha = "alpha"
+                                                  , Arm = "arm"
+                                                  , HPPA = "hppa"
+                                                  , HPPA64 = "hppa64"
+                                                  , M68k = "m68k"
+                                                  , Mips = "mips"
+                                                  , Mips64 = "mips64"
+                                                  , Mips64El = "mips64el"
+                                                  , MipsEl = "mipsel"
+                                                  , MipsIsa32r6 = "mipsisa32r6"
+                                                  , MipsIsa32r6El =
+                                                      "mipsisa32r6el"
+                                                  , MipsIsa64r6 = "mipsisa64r6"
+                                                  , MipsIsa64r6El =
+                                                      "mipsisa64r6el"
+                                                  , PowerPC = "powerpc"
+                                                  , PowerPC64 = "powerpc64"
+                                                  , PowerPC64le = "powerpc64le"
+                                                  , RISCV64 = "riscv64"
+                                                  , S390x = "s390x"
+                                                  , SH4 = "sh4"
+                                                  , Sparc64 = "sparc64"
+                                                  , X64 = "x86_64"
+                                                  , X86 = "i686"
+                                                  }
+                                                  _.arch}-${merge
+                                                              { AIX = "aix"
+                                                              , Android =
+                                                                  "android"
+                                                              , Darwin =
+                                                                  "darwin"
+                                                              , Dragonfly =
+                                                                  "dragonfly"
+                                                              , FreeBSD =
+                                                                  "freebsd"
+                                                              , Haiku = "haiku"
+                                                              , Hurd = "hurd"
+                                                              , IOS = "darwin"
+                                                              , Linux = "linux"
+                                                              , NetBSD =
+                                                                  "netbsd"
+                                                              , NoOs = "none"
+                                                              , OpenBSD =
+                                                                  "openbsd"
+                                                              , Redox = "redox"
+                                                              , Solaris =
+                                                                  "solaris"
+                                                              , Windows = "w64"
+                                                              }
+                                                              _.os}${merge
+                                                                       { None =
+                                                                           ""
+                                                                       , Some =
+                                                                           λ ( abi
+                                                                             : < GNU
+                                                                               | GNUabi64
+                                                                               | GNUeabi
+                                                                               | GNUeabihf
+                                                                               | GNUspe
+                                                                               | MinGw
+                                                                               >
+                                                                             ) →
+                                                                             "-${merge
+                                                                                   { GNU =
+                                                                                       "gnu"
+                                                                                   , GNUabi64 =
+                                                                                       "gnuabi64"
+                                                                                   , GNUeabi =
+                                                                                       "gnueabi"
+                                                                                   , GNUeabihf =
+                                                                                       "gnueabihf"
+                                                                                   , GNUspe =
+                                                                                       "gnuspe"
+                                                                                   , MinGw =
+                                                                                       "mingw32"
+                                                                                   }
+                                                                                   abi}"
+                                                                       }
+                                                                       _.abi}"
+                              }
+                              cfg.targetTriple
+                          )
+                      )
+                , environment = envVars ([] : List Text) cfg
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , configureLinkExtraLibs =
+          λ(linkLibs : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      ( merge
+                          { None = [ "--prefix=${cfg.installDir}" ]
+                          , Some =
+                              λ(x : Text) → [ "--prefix=${cfg.installDir}", x ]
+                          }
+                          ( merge
+                              { None = None Text
+                              , Some =
+                                  λ ( _
+                                    : { abi :
+                                          Optional
+                                            < GNU
+                                            | GNUabi64
+                                            | GNUeabi
+                                            | GNUeabihf
+                                            | GNUspe
+                                            | MinGw
+                                            >
+                                      , arch :
+                                          < AArch
+                                          | Alpha
+                                          | Arm
+                                          | HPPA
+                                          | HPPA64
+                                          | M68k
+                                          | Mips
+                                          | Mips64
+                                          | Mips64El
+                                          | MipsEl
+                                          | MipsIsa32r6
+                                          | MipsIsa32r6El
+                                          | MipsIsa64r6
+                                          | MipsIsa64r6El
+                                          | PowerPC
+                                          | PowerPC64
+                                          | PowerPC64le
+                                          | RISCV64
+                                          | S390x
+                                          | SH4
+                                          | Sparc64
+                                          | X64
+                                          | X86
+                                          >
+                                      , manufacturer :
+                                          Optional
+                                            < Apple | IBM | PC | Unknown >
+                                      , os :
+                                          < AIX
+                                          | Android
+                                          | Darwin
+                                          | Dragonfly
+                                          | FreeBSD
+                                          | Haiku
+                                          | Hurd
+                                          | IOS
+                                          | Linux
+                                          | NetBSD
+                                          | NoOs
+                                          | OpenBSD
+                                          | Redox
+                                          | Solaris
+                                          | Windows
+                                          >
+                                      }
+                                    ) →
+                                    Some
+                                      "--host=${merge
+                                                  { AArch = "aarch64"
+                                                  , Alpha = "alpha"
+                                                  , Arm = "arm"
+                                                  , HPPA = "hppa"
+                                                  , HPPA64 = "hppa64"
+                                                  , M68k = "m68k"
+                                                  , Mips = "mips"
+                                                  , Mips64 = "mips64"
+                                                  , Mips64El = "mips64el"
+                                                  , MipsEl = "mipsel"
+                                                  , MipsIsa32r6 = "mipsisa32r6"
+                                                  , MipsIsa32r6El =
+                                                      "mipsisa32r6el"
+                                                  , MipsIsa64r6 = "mipsisa64r6"
+                                                  , MipsIsa64r6El =
+                                                      "mipsisa64r6el"
+                                                  , PowerPC = "powerpc"
+                                                  , PowerPC64 = "powerpc64"
+                                                  , PowerPC64le = "powerpc64le"
+                                                  , RISCV64 = "riscv64"
+                                                  , S390x = "s390x"
+                                                  , SH4 = "sh4"
+                                                  , Sparc64 = "sparc64"
+                                                  , X64 = "x86_64"
+                                                  , X86 = "i686"
+                                                  }
+                                                  _.arch}-${merge
+                                                              { AIX = "aix"
+                                                              , Android =
+                                                                  "android"
+                                                              , Darwin =
+                                                                  "darwin"
+                                                              , Dragonfly =
+                                                                  "dragonfly"
+                                                              , FreeBSD =
+                                                                  "freebsd"
+                                                              , Haiku = "haiku"
+                                                              , Hurd = "hurd"
+                                                              , IOS = "darwin"
+                                                              , Linux = "linux"
+                                                              , NetBSD =
+                                                                  "netbsd"
+                                                              , NoOs = "none"
+                                                              , OpenBSD =
+                                                                  "openbsd"
+                                                              , Redox = "redox"
+                                                              , Solaris =
+                                                                  "solaris"
+                                                              , Windows = "w64"
+                                                              }
+                                                              _.os}${merge
+                                                                       { None =
+                                                                           ""
+                                                                       , Some =
+                                                                           λ ( abi
+                                                                             : < GNU
+                                                                               | GNUabi64
+                                                                               | GNUeabi
+                                                                               | GNUeabihf
+                                                                               | GNUspe
+                                                                               | MinGw
+                                                                               >
+                                                                             ) →
+                                                                             "-${merge
+                                                                                   { GNU =
+                                                                                       "gnu"
+                                                                                   , GNUabi64 =
+                                                                                       "gnuabi64"
+                                                                                   , GNUeabi =
+                                                                                       "gnueabi"
+                                                                                   , GNUeabihf =
+                                                                                       "gnueabihf"
+                                                                                   , GNUspe =
+                                                                                       "gnuspe"
+                                                                                   , MinGw =
+                                                                                       "mingw32"
+                                                                                   }
+                                                                                   abi}"
+                                                                       }
+                                                                       _.abi}"
+                              }
+                              cfg.targetTriple
+                          )
+                      )
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         linkLibs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             " -l${_@1}${_}"
+                                         )
+                                         ""}${List/fold
+                                                Text
+                                                cfg.linkDirs
+                                                Text
+                                                ( λ(_ : Text) →
+                                                  λ(_ : Text) →
+                                                    "${if    merge
+                                                               { AIX = False
+                                                               , Android = False
+                                                               , Darwin = True
+                                                               , Dragonfly =
+                                                                   False
+                                                               , FreeBSD = False
+                                                               , Haiku = False
+                                                               , Hurd = False
+                                                               , IOS = False
+                                                               , Linux = False
+                                                               , NetBSD = False
+                                                               , NoOs = False
+                                                               , OpenBSD = False
+                                                               , Redox = False
+                                                               , Solaris = False
+                                                               , Windows = False
+                                                               }
+                                                               cfg.buildOS
+                                                       then  ""
+                                                       else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                                )
+                                                ""}"
+                          , var = "LDFLAGS"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.includeDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-I${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${if cfg.static then " -static" else ""}"
+                          , var = "CPPFLAGS"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_RUN_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , configureMkExes =
+          λ(bins : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              List/fold
+                Text
+                bins
+                ( List
+                    < Call :
+                        { arguments : List Text
+                        , environment :
+                            Optional (List { value : Text, var : Text })
+                        , procDir : Optional Text
+                        , program : Text
+                        }
+                    | CopyFile : { dest : Text, src : Text }
+                    | CreateDirectory : { dir : Text }
+                    | MakeExecutable : { file : Text }
+                    | Patch : { patchContents : Text }
+                    | Symlink : { linkName : Text, tgt : Text }
+                    | SymlinkBinary : { file : Text }
+                    | SymlinkManpage : { file : Text, section : Natural }
+                    | Write : { contents : Text, file : Text }
+                    >
+                )
+                ( λ(_ : Text) →
+                  λ ( _
+                    : List
+                        < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >
+                    ) →
+                      [ < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >.MakeExecutable
+                          { file = _@1 }
+                      ]
+                    # _
+                )
+                ( [] : List
+                         < Call :
+                             { arguments : List Text
+                             , environment :
+                                 Optional (List { value : Text, var : Text })
+                             , procDir : Optional Text
+                             , program : Text
+                             }
+                         | CopyFile : { dest : Text, src : Text }
+                         | CreateDirectory : { dir : Text }
+                         | MakeExecutable : { file : Text }
+                         | Patch : { patchContents : Text }
+                         | Symlink : { linkName : Text, tgt : Text }
+                         | SymlinkBinary : { file : Text }
+                         | SymlinkManpage : { file : Text, section : Natural }
+                         | Write : { contents : Text, file : Text }
+                         >
+                )
+            # [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                      ( if    merge
+                                { AIX = False
+                                , Android = False
+                                , Darwin = True
+                                , Dragonfly = False
+                                , FreeBSD = False
+                                , Haiku = False
+                                , Hurd = False
+                                , IOS = False
+                                , Linux = False
+                                , NetBSD = False
+                                , NoOs = False
+                                , OpenBSD = False
+                                , Redox = False
+                                , Solaris = False
+                                , Windows = False
+                                }
+                                cfg.buildOS
+                        then  λ(x : List Text) → [ "configure" ] # x
+                        else  λ(x : List Text) → x
+                      )
+                        ( merge
+                            { None = [ "--prefix=${cfg.installDir}" ]
+                            , Some =
+                                λ(x : Text) →
+                                  [ "--prefix=${cfg.installDir}", x ]
+                            }
+                            ( merge
+                                { None = None Text
+                                , Some =
+                                    λ ( _
+                                      : { abi :
+                                            Optional
+                                              < GNU
+                                              | GNUabi64
+                                              | GNUeabi
+                                              | GNUeabihf
+                                              | GNUspe
+                                              | MinGw
+                                              >
+                                        , arch :
+                                            < AArch
+                                            | Alpha
+                                            | Arm
+                                            | HPPA
+                                            | HPPA64
+                                            | M68k
+                                            | Mips
+                                            | Mips64
+                                            | Mips64El
+                                            | MipsEl
+                                            | MipsIsa32r6
+                                            | MipsIsa32r6El
+                                            | MipsIsa64r6
+                                            | MipsIsa64r6El
+                                            | PowerPC
+                                            | PowerPC64
+                                            | PowerPC64le
+                                            | RISCV64
+                                            | S390x
+                                            | SH4
+                                            | Sparc64
+                                            | X64
+                                            | X86
+                                            >
+                                        , manufacturer :
+                                            Optional
+                                              < Apple | IBM | PC | Unknown >
+                                        , os :
+                                            < AIX
+                                            | Android
+                                            | Darwin
+                                            | Dragonfly
+                                            | FreeBSD
+                                            | Haiku
+                                            | Hurd
+                                            | IOS
+                                            | Linux
+                                            | NetBSD
+                                            | NoOs
+                                            | OpenBSD
+                                            | Redox
+                                            | Solaris
+                                            | Windows
+                                            >
+                                        }
+                                      ) →
+                                      Some
+                                        "--host=${merge
+                                                    { AArch = "aarch64"
+                                                    , Alpha = "alpha"
+                                                    , Arm = "arm"
+                                                    , HPPA = "hppa"
+                                                    , HPPA64 = "hppa64"
+                                                    , M68k = "m68k"
+                                                    , Mips = "mips"
+                                                    , Mips64 = "mips64"
+                                                    , Mips64El = "mips64el"
+                                                    , MipsEl = "mipsel"
+                                                    , MipsIsa32r6 =
+                                                        "mipsisa32r6"
+                                                    , MipsIsa32r6El =
+                                                        "mipsisa32r6el"
+                                                    , MipsIsa64r6 =
+                                                        "mipsisa64r6"
+                                                    , MipsIsa64r6El =
+                                                        "mipsisa64r6el"
+                                                    , PowerPC = "powerpc"
+                                                    , PowerPC64 = "powerpc64"
+                                                    , PowerPC64le =
+                                                        "powerpc64le"
+                                                    , RISCV64 = "riscv64"
+                                                    , S390x = "s390x"
+                                                    , SH4 = "sh4"
+                                                    , Sparc64 = "sparc64"
+                                                    , X64 = "x86_64"
+                                                    , X86 = "i686"
+                                                    }
+                                                    _.arch}-${merge
+                                                                { AIX = "aix"
+                                                                , Android =
+                                                                    "android"
+                                                                , Darwin =
+                                                                    "darwin"
+                                                                , Dragonfly =
+                                                                    "dragonfly"
+                                                                , FreeBSD =
+                                                                    "freebsd"
+                                                                , Haiku =
+                                                                    "haiku"
+                                                                , Hurd = "hurd"
+                                                                , IOS = "darwin"
+                                                                , Linux =
+                                                                    "linux"
+                                                                , NetBSD =
+                                                                    "netbsd"
+                                                                , NoOs = "none"
+                                                                , OpenBSD =
+                                                                    "openbsd"
+                                                                , Redox =
+                                                                    "redox"
+                                                                , Solaris =
+                                                                    "solaris"
+                                                                , Windows =
+                                                                    "w64"
+                                                                }
+                                                                _.os}${merge
+                                                                         { None =
+                                                                             ""
+                                                                         , Some =
+                                                                             λ ( abi
+                                                                               : < GNU
+                                                                                 | GNUabi64
+                                                                                 | GNUeabi
+                                                                                 | GNUeabihf
+                                                                                 | GNUspe
+                                                                                 | MinGw
+                                                                                 >
+                                                                               ) →
+                                                                               "-${merge
+                                                                                     { GNU =
+                                                                                         "gnu"
+                                                                                     , GNUabi64 =
+                                                                                         "gnuabi64"
+                                                                                     , GNUeabi =
+                                                                                         "gnueabi"
+                                                                                     , GNUeabihf =
+                                                                                         "gnueabihf"
+                                                                                     , GNUspe =
+                                                                                         "gnuspe"
+                                                                                     , MinGw =
+                                                                                         "mingw32"
+                                                                                     }
+                                                                                     abi}"
+                                                                         }
+                                                                         _.abi}"
+                                }
+                                cfg.targetTriple
+                            )
+                        )
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.includeDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-I${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${if cfg.static then " -static" else ""}"
+                            , var = "CPPFLAGS"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , if    cfg.static
+                            then  { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/lib:/lib:/usr/lib"
+                                  , var = "LIBRARY_PATH"
+                                  }
+                            else  { value =
+                                      merge
+                                        { Empty = ""
+                                        , NonEmpty = λ(_ : Text) → _
+                                        }
+                                        ( List/fold
+                                            Text
+                                            cfg.linkDirs
+                                            < Empty | NonEmpty : Text >
+                                            ( λ(_ : Text) →
+                                              λ ( _
+                                                : < Empty | NonEmpty : Text >
+                                                ) →
+                                                merge
+                                                  { Empty =
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        _@1
+                                                  , NonEmpty =
+                                                      λ(_ : Text) →
+                                                        < Empty
+                                                        | NonEmpty : Text
+                                                        >.NonEmpty
+                                                          "${_@2}:${_}"
+                                                  }
+                                                  _
+                                            )
+                                            < Empty | NonEmpty : Text >.Empty
+                                        )
+                                  , var = "LD_LIBRARY_PATH"
+                                  }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_RUN_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  "sh"
+                      else  "./configure"
+                  }
+              ]
+      , configureMkExesExtraFlags =
+          λ(x : { bins : List Text, extraFlags : List Text }) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              List/fold
+                Text
+                x.bins
+                ( List
+                    < Call :
+                        { arguments : List Text
+                        , environment :
+                            Optional (List { value : Text, var : Text })
+                        , procDir : Optional Text
+                        , program : Text
+                        }
+                    | CopyFile : { dest : Text, src : Text }
+                    | CreateDirectory : { dir : Text }
+                    | MakeExecutable : { file : Text }
+                    | Patch : { patchContents : Text }
+                    | Symlink : { linkName : Text, tgt : Text }
+                    | SymlinkBinary : { file : Text }
+                    | SymlinkManpage : { file : Text, section : Natural }
+                    | Write : { contents : Text, file : Text }
+                    >
+                )
+                ( λ(_ : Text) →
+                  λ ( _
+                    : List
+                        < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >
+                    ) →
+                      [ < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >.MakeExecutable
+                          { file = _@1 }
+                      ]
+                    # _
+                )
+                ( [] : List
+                         < Call :
+                             { arguments : List Text
+                             , environment :
+                                 Optional (List { value : Text, var : Text })
+                             , procDir : Optional Text
+                             , program : Text
+                             }
+                         | CopyFile : { dest : Text, src : Text }
+                         | CreateDirectory : { dir : Text }
+                         | MakeExecutable : { file : Text }
+                         | Patch : { patchContents : Text }
+                         | Symlink : { linkName : Text, tgt : Text }
+                         | SymlinkBinary : { file : Text }
+                         | SymlinkManpage : { file : Text, section : Natural }
+                         | Write : { contents : Text, file : Text }
+                         >
+                )
+            # [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                      ( if    merge
+                                { AIX = False
+                                , Android = False
+                                , Darwin = True
+                                , Dragonfly = False
+                                , FreeBSD = False
+                                , Haiku = False
+                                , Hurd = False
+                                , IOS = False
+                                , Linux = False
+                                , NetBSD = False
+                                , NoOs = False
+                                , OpenBSD = False
+                                , Redox = False
+                                , Solaris = False
+                                , Windows = False
+                                }
+                                cfg.buildOS
+                        then  λ(x : List Text) → [ "configure" ] # x
+                        else  λ(x : List Text) → x
+                      )
+                        (   merge
+                              { None = [ "--prefix=${cfg.installDir}" ]
+                              , Some =
+                                  λ(x : Text) →
+                                    [ "--prefix=${cfg.installDir}", x ]
+                              }
+                              ( merge
+                                  { None = None Text
+                                  , Some =
+                                      λ ( _
+                                        : { abi :
+                                              Optional
+                                                < GNU
+                                                | GNUabi64
+                                                | GNUeabi
+                                                | GNUeabihf
+                                                | GNUspe
+                                                | MinGw
+                                                >
+                                          , arch :
+                                              < AArch
+                                              | Alpha
+                                              | Arm
+                                              | HPPA
+                                              | HPPA64
+                                              | M68k
+                                              | Mips
+                                              | Mips64
+                                              | Mips64El
+                                              | MipsEl
+                                              | MipsIsa32r6
+                                              | MipsIsa32r6El
+                                              | MipsIsa64r6
+                                              | MipsIsa64r6El
+                                              | PowerPC
+                                              | PowerPC64
+                                              | PowerPC64le
+                                              | RISCV64
+                                              | S390x
+                                              | SH4
+                                              | Sparc64
+                                              | X64
+                                              | X86
+                                              >
+                                          , manufacturer :
+                                              Optional
+                                                < Apple | IBM | PC | Unknown >
+                                          , os :
+                                              < AIX
+                                              | Android
+                                              | Darwin
+                                              | Dragonfly
+                                              | FreeBSD
+                                              | Haiku
+                                              | Hurd
+                                              | IOS
+                                              | Linux
+                                              | NetBSD
+                                              | NoOs
+                                              | OpenBSD
+                                              | Redox
+                                              | Solaris
+                                              | Windows
+                                              >
+                                          }
+                                        ) →
+                                        Some
+                                          "--host=${merge
+                                                      { AArch = "aarch64"
+                                                      , Alpha = "alpha"
+                                                      , Arm = "arm"
+                                                      , HPPA = "hppa"
+                                                      , HPPA64 = "hppa64"
+                                                      , M68k = "m68k"
+                                                      , Mips = "mips"
+                                                      , Mips64 = "mips64"
+                                                      , Mips64El = "mips64el"
+                                                      , MipsEl = "mipsel"
+                                                      , MipsIsa32r6 =
+                                                          "mipsisa32r6"
+                                                      , MipsIsa32r6El =
+                                                          "mipsisa32r6el"
+                                                      , MipsIsa64r6 =
+                                                          "mipsisa64r6"
+                                                      , MipsIsa64r6El =
+                                                          "mipsisa64r6el"
+                                                      , PowerPC = "powerpc"
+                                                      , PowerPC64 = "powerpc64"
+                                                      , PowerPC64le =
+                                                          "powerpc64le"
+                                                      , RISCV64 = "riscv64"
+                                                      , S390x = "s390x"
+                                                      , SH4 = "sh4"
+                                                      , Sparc64 = "sparc64"
+                                                      , X64 = "x86_64"
+                                                      , X86 = "i686"
+                                                      }
+                                                      _.arch}-${merge
+                                                                  { AIX = "aix"
+                                                                  , Android =
+                                                                      "android"
+                                                                  , Darwin =
+                                                                      "darwin"
+                                                                  , Dragonfly =
+                                                                      "dragonfly"
+                                                                  , FreeBSD =
+                                                                      "freebsd"
+                                                                  , Haiku =
+                                                                      "haiku"
+                                                                  , Hurd =
+                                                                      "hurd"
+                                                                  , IOS =
+                                                                      "darwin"
+                                                                  , Linux =
+                                                                      "linux"
+                                                                  , NetBSD =
+                                                                      "netbsd"
+                                                                  , NoOs =
+                                                                      "none"
+                                                                  , OpenBSD =
+                                                                      "openbsd"
+                                                                  , Redox =
+                                                                      "redox"
+                                                                  , Solaris =
+                                                                      "solaris"
+                                                                  , Windows =
+                                                                      "w64"
+                                                                  }
+                                                                  _.os}${merge
+                                                                           { None =
+                                                                               ""
+                                                                           , Some =
+                                                                               λ ( abi
+                                                                                 : < GNU
+                                                                                   | GNUabi64
+                                                                                   | GNUeabi
+                                                                                   | GNUeabihf
+                                                                                   | GNUspe
+                                                                                   | MinGw
+                                                                                   >
+                                                                                 ) →
+                                                                                 "-${merge
+                                                                                       { GNU =
+                                                                                           "gnu"
+                                                                                       , GNUabi64 =
+                                                                                           "gnuabi64"
+                                                                                       , GNUeabi =
+                                                                                           "gnueabi"
+                                                                                       , GNUeabihf =
+                                                                                           "gnueabihf"
+                                                                                       , GNUspe =
+                                                                                           "gnuspe"
+                                                                                       , MinGw =
+                                                                                           "mingw32"
+                                                                                       }
+                                                                                       abi}"
+                                                                           }
+                                                                           _.abi}"
+                                  }
+                                  cfg.targetTriple
+                              )
+                          # x.extraFlags
+                        )
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.includeDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-I${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${if cfg.static then " -static" else ""}"
+                            , var = "CPPFLAGS"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , if    cfg.static
+                            then  { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/lib:/lib:/usr/lib"
+                                  , var = "LIBRARY_PATH"
+                                  }
+                            else  { value =
+                                      merge
+                                        { Empty = ""
+                                        , NonEmpty = λ(_ : Text) → _
+                                        }
+                                        ( List/fold
+                                            Text
+                                            cfg.linkDirs
+                                            < Empty | NonEmpty : Text >
+                                            ( λ(_ : Text) →
+                                              λ ( _
+                                                : < Empty | NonEmpty : Text >
+                                                ) →
+                                                merge
+                                                  { Empty =
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        _@1
+                                                  , NonEmpty =
+                                                      λ(_ : Text) →
+                                                        < Empty
+                                                        | NonEmpty : Text
+                                                        >.NonEmpty
+                                                          "${_@2}:${_}"
+                                                  }
+                                                  _
+                                            )
+                                            < Empty | NonEmpty : Text >.Empty
+                                        )
+                                  , var = "LD_LIBRARY_PATH"
+                                  }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_RUN_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  "sh"
+                      else  "./configure"
+                  }
+              ]
+      , configureWithFlags =
+          λ(extraFlags : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      (   merge
+                            { None = [ "--prefix=${cfg.installDir}" ]
+                            , Some =
+                                λ(x : Text) →
+                                  [ "--prefix=${cfg.installDir}", x ]
+                            }
+                            ( merge
+                                { None = None Text
+                                , Some =
+                                    λ ( _
+                                      : { abi :
+                                            Optional
+                                              < GNU
+                                              | GNUabi64
+                                              | GNUeabi
+                                              | GNUeabihf
+                                              | GNUspe
+                                              | MinGw
+                                              >
+                                        , arch :
+                                            < AArch
+                                            | Alpha
+                                            | Arm
+                                            | HPPA
+                                            | HPPA64
+                                            | M68k
+                                            | Mips
+                                            | Mips64
+                                            | Mips64El
+                                            | MipsEl
+                                            | MipsIsa32r6
+                                            | MipsIsa32r6El
+                                            | MipsIsa64r6
+                                            | MipsIsa64r6El
+                                            | PowerPC
+                                            | PowerPC64
+                                            | PowerPC64le
+                                            | RISCV64
+                                            | S390x
+                                            | SH4
+                                            | Sparc64
+                                            | X64
+                                            | X86
+                                            >
+                                        , manufacturer :
+                                            Optional
+                                              < Apple | IBM | PC | Unknown >
+                                        , os :
+                                            < AIX
+                                            | Android
+                                            | Darwin
+                                            | Dragonfly
+                                            | FreeBSD
+                                            | Haiku
+                                            | Hurd
+                                            | IOS
+                                            | Linux
+                                            | NetBSD
+                                            | NoOs
+                                            | OpenBSD
+                                            | Redox
+                                            | Solaris
+                                            | Windows
+                                            >
+                                        }
+                                      ) →
+                                      Some
+                                        "--host=${merge
+                                                    { AArch = "aarch64"
+                                                    , Alpha = "alpha"
+                                                    , Arm = "arm"
+                                                    , HPPA = "hppa"
+                                                    , HPPA64 = "hppa64"
+                                                    , M68k = "m68k"
+                                                    , Mips = "mips"
+                                                    , Mips64 = "mips64"
+                                                    , Mips64El = "mips64el"
+                                                    , MipsEl = "mipsel"
+                                                    , MipsIsa32r6 =
+                                                        "mipsisa32r6"
+                                                    , MipsIsa32r6El =
+                                                        "mipsisa32r6el"
+                                                    , MipsIsa64r6 =
+                                                        "mipsisa64r6"
+                                                    , MipsIsa64r6El =
+                                                        "mipsisa64r6el"
+                                                    , PowerPC = "powerpc"
+                                                    , PowerPC64 = "powerpc64"
+                                                    , PowerPC64le =
+                                                        "powerpc64le"
+                                                    , RISCV64 = "riscv64"
+                                                    , S390x = "s390x"
+                                                    , SH4 = "sh4"
+                                                    , Sparc64 = "sparc64"
+                                                    , X64 = "x86_64"
+                                                    , X86 = "i686"
+                                                    }
+                                                    _.arch}-${merge
+                                                                { AIX = "aix"
+                                                                , Android =
+                                                                    "android"
+                                                                , Darwin =
+                                                                    "darwin"
+                                                                , Dragonfly =
+                                                                    "dragonfly"
+                                                                , FreeBSD =
+                                                                    "freebsd"
+                                                                , Haiku =
+                                                                    "haiku"
+                                                                , Hurd = "hurd"
+                                                                , IOS = "darwin"
+                                                                , Linux =
+                                                                    "linux"
+                                                                , NetBSD =
+                                                                    "netbsd"
+                                                                , NoOs = "none"
+                                                                , OpenBSD =
+                                                                    "openbsd"
+                                                                , Redox =
+                                                                    "redox"
+                                                                , Solaris =
+                                                                    "solaris"
+                                                                , Windows =
+                                                                    "w64"
+                                                                }
+                                                                _.os}${merge
+                                                                         { None =
+                                                                             ""
+                                                                         , Some =
+                                                                             λ ( abi
+                                                                               : < GNU
+                                                                                 | GNUabi64
+                                                                                 | GNUeabi
+                                                                                 | GNUeabihf
+                                                                                 | GNUspe
+                                                                                 | MinGw
+                                                                                 >
+                                                                               ) →
+                                                                               "-${merge
+                                                                                     { GNU =
+                                                                                         "gnu"
+                                                                                     , GNUabi64 =
+                                                                                         "gnuabi64"
+                                                                                     , GNUeabi =
+                                                                                         "gnueabi"
+                                                                                     , GNUeabihf =
+                                                                                         "gnueabihf"
+                                                                                     , GNUspe =
+                                                                                         "gnuspe"
+                                                                                     , MinGw =
+                                                                                         "mingw32"
+                                                                                     }
+                                                                                     abi}"
+                                                                         }
+                                                                         _.abi}"
+                                }
+                                cfg.targetTriple
+                            )
+                        # extraFlags
+                      )
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.includeDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-I${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${if cfg.static then " -static" else ""}"
+                          , var = "CPPFLAGS"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_RUN_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , configureWithPatch =
+          λ(p : Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Patch
+                { patchContents = p }
+            , < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      ( merge
+                          { None = [ "--prefix=${cfg.installDir}" ]
+                          , Some =
+                              λ(x : Text) → [ "--prefix=${cfg.installDir}", x ]
+                          }
+                          ( merge
+                              { None = None Text
+                              , Some =
+                                  λ ( _
+                                    : { abi :
+                                          Optional
+                                            < GNU
+                                            | GNUabi64
+                                            | GNUeabi
+                                            | GNUeabihf
+                                            | GNUspe
+                                            | MinGw
+                                            >
+                                      , arch :
+                                          < AArch
+                                          | Alpha
+                                          | Arm
+                                          | HPPA
+                                          | HPPA64
+                                          | M68k
+                                          | Mips
+                                          | Mips64
+                                          | Mips64El
+                                          | MipsEl
+                                          | MipsIsa32r6
+                                          | MipsIsa32r6El
+                                          | MipsIsa64r6
+                                          | MipsIsa64r6El
+                                          | PowerPC
+                                          | PowerPC64
+                                          | PowerPC64le
+                                          | RISCV64
+                                          | S390x
+                                          | SH4
+                                          | Sparc64
+                                          | X64
+                                          | X86
+                                          >
+                                      , manufacturer :
+                                          Optional
+                                            < Apple | IBM | PC | Unknown >
+                                      , os :
+                                          < AIX
+                                          | Android
+                                          | Darwin
+                                          | Dragonfly
+                                          | FreeBSD
+                                          | Haiku
+                                          | Hurd
+                                          | IOS
+                                          | Linux
+                                          | NetBSD
+                                          | NoOs
+                                          | OpenBSD
+                                          | Redox
+                                          | Solaris
+                                          | Windows
+                                          >
+                                      }
+                                    ) →
+                                    Some
+                                      "--host=${merge
+                                                  { AArch = "aarch64"
+                                                  , Alpha = "alpha"
+                                                  , Arm = "arm"
+                                                  , HPPA = "hppa"
+                                                  , HPPA64 = "hppa64"
+                                                  , M68k = "m68k"
+                                                  , Mips = "mips"
+                                                  , Mips64 = "mips64"
+                                                  , Mips64El = "mips64el"
+                                                  , MipsEl = "mipsel"
+                                                  , MipsIsa32r6 = "mipsisa32r6"
+                                                  , MipsIsa32r6El =
+                                                      "mipsisa32r6el"
+                                                  , MipsIsa64r6 = "mipsisa64r6"
+                                                  , MipsIsa64r6El =
+                                                      "mipsisa64r6el"
+                                                  , PowerPC = "powerpc"
+                                                  , PowerPC64 = "powerpc64"
+                                                  , PowerPC64le = "powerpc64le"
+                                                  , RISCV64 = "riscv64"
+                                                  , S390x = "s390x"
+                                                  , SH4 = "sh4"
+                                                  , Sparc64 = "sparc64"
+                                                  , X64 = "x86_64"
+                                                  , X86 = "i686"
+                                                  }
+                                                  _.arch}-${merge
+                                                              { AIX = "aix"
+                                                              , Android =
+                                                                  "android"
+                                                              , Darwin =
+                                                                  "darwin"
+                                                              , Dragonfly =
+                                                                  "dragonfly"
+                                                              , FreeBSD =
+                                                                  "freebsd"
+                                                              , Haiku = "haiku"
+                                                              , Hurd = "hurd"
+                                                              , IOS = "darwin"
+                                                              , Linux = "linux"
+                                                              , NetBSD =
+                                                                  "netbsd"
+                                                              , NoOs = "none"
+                                                              , OpenBSD =
+                                                                  "openbsd"
+                                                              , Redox = "redox"
+                                                              , Solaris =
+                                                                  "solaris"
+                                                              , Windows = "w64"
+                                                              }
+                                                              _.os}${merge
+                                                                       { None =
+                                                                           ""
+                                                                       , Some =
+                                                                           λ ( abi
+                                                                             : < GNU
+                                                                               | GNUabi64
+                                                                               | GNUeabi
+                                                                               | GNUeabihf
+                                                                               | GNUspe
+                                                                               | MinGw
+                                                                               >
+                                                                             ) →
+                                                                             "-${merge
+                                                                                   { GNU =
+                                                                                       "gnu"
+                                                                                   , GNUabi64 =
+                                                                                       "gnuabi64"
+                                                                                   , GNUeabi =
+                                                                                       "gnueabi"
+                                                                                   , GNUeabihf =
+                                                                                       "gnueabihf"
+                                                                                   , GNUspe =
+                                                                                       "gnuspe"
+                                                                                   , MinGw =
+                                                                                       "mingw32"
+                                                                                   }
+                                                                                   abi}"
+                                                                       }
+                                                                       _.abi}"
+                              }
+                              cfg.targetTriple
+                          )
+                      )
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.includeDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-I${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${if cfg.static then " -static" else ""}"
+                          , var = "CPPFLAGS"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_RUN_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , configureWithPatches =
+          λ(patches : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+              List/fold
+                Text
+                patches
+                ( List
+                    < Call :
+                        { arguments : List Text
+                        , environment :
+                            Optional (List { value : Text, var : Text })
+                        , procDir : Optional Text
+                        , program : Text
+                        }
+                    | CopyFile : { dest : Text, src : Text }
+                    | CreateDirectory : { dir : Text }
+                    | MakeExecutable : { file : Text }
+                    | Patch : { patchContents : Text }
+                    | Symlink : { linkName : Text, tgt : Text }
+                    | SymlinkBinary : { file : Text }
+                    | SymlinkManpage : { file : Text, section : Natural }
+                    | Write : { contents : Text, file : Text }
+                    >
+                )
+                ( λ(_ : Text) →
+                  λ ( _
+                    : List
+                        < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >
+                    ) →
+                      [ < Call :
+                            { arguments : List Text
+                            , environment :
+                                Optional (List { value : Text, var : Text })
+                            , procDir : Optional Text
+                            , program : Text
+                            }
+                        | CopyFile : { dest : Text, src : Text }
+                        | CreateDirectory : { dir : Text }
+                        | MakeExecutable : { file : Text }
+                        | Patch : { patchContents : Text }
+                        | Symlink : { linkName : Text, tgt : Text }
+                        | SymlinkBinary : { file : Text }
+                        | SymlinkManpage : { file : Text, section : Natural }
+                        | Write : { contents : Text, file : Text }
+                        >.Patch
+                          { patchContents = _@1 }
+                      ]
+                    # _
+                )
+                ( [] : List
+                         < Call :
+                             { arguments : List Text
+                             , environment :
+                                 Optional (List { value : Text, var : Text })
+                             , procDir : Optional Text
+                             , program : Text
+                             }
+                         | CopyFile : { dest : Text, src : Text }
+                         | CreateDirectory : { dir : Text }
+                         | MakeExecutable : { file : Text }
+                         | Patch : { patchContents : Text }
+                         | Symlink : { linkName : Text, tgt : Text }
+                         | SymlinkBinary : { file : Text }
+                         | SymlinkManpage : { file : Text, section : Natural }
+                         | Write : { contents : Text, file : Text }
+                         >
+                )
+            # [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                      ( if    merge
+                                { AIX = False
+                                , Android = False
+                                , Darwin = True
+                                , Dragonfly = False
+                                , FreeBSD = False
+                                , Haiku = False
+                                , Hurd = False
+                                , IOS = False
+                                , Linux = False
+                                , NetBSD = False
+                                , NoOs = False
+                                , OpenBSD = False
+                                , Redox = False
+                                , Solaris = False
+                                , Windows = False
+                                }
+                                cfg.buildOS
+                        then  λ(x : List Text) → [ "configure" ] # x
+                        else  λ(x : List Text) → x
+                      )
+                        ( merge
+                            { None = [ "--prefix=${cfg.installDir}" ]
+                            , Some =
+                                λ(x : Text) →
+                                  [ "--prefix=${cfg.installDir}", x ]
+                            }
+                            ( merge
+                                { None = None Text
+                                , Some =
+                                    λ ( _
+                                      : { abi :
+                                            Optional
+                                              < GNU
+                                              | GNUabi64
+                                              | GNUeabi
+                                              | GNUeabihf
+                                              | GNUspe
+                                              | MinGw
+                                              >
+                                        , arch :
+                                            < AArch
+                                            | Alpha
+                                            | Arm
+                                            | HPPA
+                                            | HPPA64
+                                            | M68k
+                                            | Mips
+                                            | Mips64
+                                            | Mips64El
+                                            | MipsEl
+                                            | MipsIsa32r6
+                                            | MipsIsa32r6El
+                                            | MipsIsa64r6
+                                            | MipsIsa64r6El
+                                            | PowerPC
+                                            | PowerPC64
+                                            | PowerPC64le
+                                            | RISCV64
+                                            | S390x
+                                            | SH4
+                                            | Sparc64
+                                            | X64
+                                            | X86
+                                            >
+                                        , manufacturer :
+                                            Optional
+                                              < Apple | IBM | PC | Unknown >
+                                        , os :
+                                            < AIX
+                                            | Android
+                                            | Darwin
+                                            | Dragonfly
+                                            | FreeBSD
+                                            | Haiku
+                                            | Hurd
+                                            | IOS
+                                            | Linux
+                                            | NetBSD
+                                            | NoOs
+                                            | OpenBSD
+                                            | Redox
+                                            | Solaris
+                                            | Windows
+                                            >
+                                        }
+                                      ) →
+                                      Some
+                                        "--host=${merge
+                                                    { AArch = "aarch64"
+                                                    , Alpha = "alpha"
+                                                    , Arm = "arm"
+                                                    , HPPA = "hppa"
+                                                    , HPPA64 = "hppa64"
+                                                    , M68k = "m68k"
+                                                    , Mips = "mips"
+                                                    , Mips64 = "mips64"
+                                                    , Mips64El = "mips64el"
+                                                    , MipsEl = "mipsel"
+                                                    , MipsIsa32r6 =
+                                                        "mipsisa32r6"
+                                                    , MipsIsa32r6El =
+                                                        "mipsisa32r6el"
+                                                    , MipsIsa64r6 =
+                                                        "mipsisa64r6"
+                                                    , MipsIsa64r6El =
+                                                        "mipsisa64r6el"
+                                                    , PowerPC = "powerpc"
+                                                    , PowerPC64 = "powerpc64"
+                                                    , PowerPC64le =
+                                                        "powerpc64le"
+                                                    , RISCV64 = "riscv64"
+                                                    , S390x = "s390x"
+                                                    , SH4 = "sh4"
+                                                    , Sparc64 = "sparc64"
+                                                    , X64 = "x86_64"
+                                                    , X86 = "i686"
+                                                    }
+                                                    _.arch}-${merge
+                                                                { AIX = "aix"
+                                                                , Android =
+                                                                    "android"
+                                                                , Darwin =
+                                                                    "darwin"
+                                                                , Dragonfly =
+                                                                    "dragonfly"
+                                                                , FreeBSD =
+                                                                    "freebsd"
+                                                                , Haiku =
+                                                                    "haiku"
+                                                                , Hurd = "hurd"
+                                                                , IOS = "darwin"
+                                                                , Linux =
+                                                                    "linux"
+                                                                , NetBSD =
+                                                                    "netbsd"
+                                                                , NoOs = "none"
+                                                                , OpenBSD =
+                                                                    "openbsd"
+                                                                , Redox =
+                                                                    "redox"
+                                                                , Solaris =
+                                                                    "solaris"
+                                                                , Windows =
+                                                                    "w64"
+                                                                }
+                                                                _.os}${merge
+                                                                         { None =
+                                                                             ""
+                                                                         , Some =
+                                                                             λ ( abi
+                                                                               : < GNU
+                                                                                 | GNUabi64
+                                                                                 | GNUeabi
+                                                                                 | GNUeabihf
+                                                                                 | GNUspe
+                                                                                 | MinGw
+                                                                                 >
+                                                                               ) →
+                                                                               "-${merge
+                                                                                     { GNU =
+                                                                                         "gnu"
+                                                                                     , GNUabi64 =
+                                                                                         "gnuabi64"
+                                                                                     , GNUeabi =
+                                                                                         "gnueabi"
+                                                                                     , GNUeabihf =
+                                                                                         "gnueabihf"
+                                                                                     , GNUspe =
+                                                                                         "gnuspe"
+                                                                                     , MinGw =
+                                                                                         "mingw32"
+                                                                                     }
+                                                                                     abi}"
+                                                                         }
+                                                                         _.abi}"
+                                }
+                                cfg.targetTriple
+                            )
+                        )
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.includeDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-I${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${if cfg.static then " -static" else ""}"
+                            , var = "CPPFLAGS"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , if    cfg.static
+                            then  { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/lib:/lib:/usr/lib"
+                                  , var = "LIBRARY_PATH"
+                                  }
+                            else  { value =
+                                      merge
+                                        { Empty = ""
+                                        , NonEmpty = λ(_ : Text) → _
+                                        }
+                                        ( List/fold
+                                            Text
+                                            cfg.linkDirs
+                                            < Empty | NonEmpty : Text >
+                                            ( λ(_ : Text) →
+                                              λ ( _
+                                                : < Empty | NonEmpty : Text >
+                                                ) →
+                                                merge
+                                                  { Empty =
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        _@1
+                                                  , NonEmpty =
+                                                      λ(_ : Text) →
+                                                        < Empty
+                                                        | NonEmpty : Text
+                                                        >.NonEmpty
+                                                          "${_@2}:${_}"
+                                                  }
+                                                  _
+                                            )
+                                            < Empty | NonEmpty : Text >.Empty
+                                        )
+                                  , var = "LD_LIBRARY_PATH"
+                                  }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_RUN_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  "sh"
+                      else  "./configure"
+                  }
+              ]
+      , copyFile =
+          λ(src : Text) →
+          λ(dest : Text) →
+            < Call :
+                { arguments : List Text
+                , environment : Optional (List { value : Text, var : Text })
+                , procDir : Optional Text
+                , program : Text
+                }
+            | CopyFile : { dest : Text, src : Text }
+            | CreateDirectory : { dir : Text }
+            | MakeExecutable : { file : Text }
+            | Patch : { patchContents : Text }
+            | Symlink : { linkName : Text, tgt : Text }
+            | SymlinkBinary : { file : Text }
+            | SymlinkManpage : { file : Text, section : Natural }
+            | Write : { contents : Text, file : Text }
+            >.CopyFile
+              { dest, src }
+      , copyFiles =
+          λ(_ : List { dest : Text, src : Text }) →
+            List/fold
+              { dest : Text, src : Text }
+              _
+              ( List
+                  < Call :
+                      { arguments : List Text
+                      , environment :
+                          Optional (List { value : Text, var : Text })
+                      , procDir : Optional Text
+                      , program : Text
+                      }
+                  | CopyFile : { dest : Text, src : Text }
+                  | CreateDirectory : { dir : Text }
+                  | MakeExecutable : { file : Text }
+                  | Patch : { patchContents : Text }
+                  | Symlink : { linkName : Text, tgt : Text }
+                  | SymlinkBinary : { file : Text }
+                  | SymlinkManpage : { file : Text, section : Natural }
+                  | Write : { contents : Text, file : Text }
+                  >
+              )
+              ( λ(_ : { dest : Text, src : Text }) →
+                λ ( _
+                  : List
+                      < Call :
+                          { arguments : List Text
+                          , environment :
+                              Optional (List { value : Text, var : Text })
+                          , procDir : Optional Text
+                          , program : Text
+                          }
+                      | CopyFile : { dest : Text, src : Text }
+                      | CreateDirectory : { dir : Text }
+                      | MakeExecutable : { file : Text }
+                      | Patch : { patchContents : Text }
+                      | Symlink : { linkName : Text, tgt : Text }
+                      | SymlinkBinary : { file : Text }
+                      | SymlinkManpage : { file : Text, section : Natural }
+                      | Write : { contents : Text, file : Text }
+                      >
+                  ) →
+                    [ < Call :
+                          { arguments : List Text
+                          , environment :
+                              Optional (List { value : Text, var : Text })
+                          , procDir : Optional Text
+                          , program : Text
+                          }
+                      | CopyFile : { dest : Text, src : Text }
+                      | CreateDirectory : { dir : Text }
+                      | MakeExecutable : { file : Text }
+                      | Patch : { patchContents : Text }
+                      | Symlink : { linkName : Text, tgt : Text }
+                      | SymlinkBinary : { file : Text }
+                      | SymlinkManpage : { file : Text, section : Natural }
+                      | Write : { contents : Text, file : Text }
+                      >.CopyFile
+                        _@1
+                    ]
+                  # _
+              )
+              ( [] : List
+                       < Call :
+                           { arguments : List Text
+                           , environment :
+                               Optional (List { value : Text, var : Text })
+                           , procDir : Optional Text
+                           , program : Text
+                           }
+                       | CopyFile : { dest : Text, src : Text }
+                       | CreateDirectory : { dir : Text }
+                       | MakeExecutable : { file : Text }
+                       | Patch : { patchContents : Text }
+                       | Symlink : { linkName : Text, tgt : Text }
+                       | SymlinkBinary : { file : Text }
+                       | SymlinkManpage : { file : Text, section : Natural }
+                       | Write : { contents : Text, file : Text }
+                       >
+              )
+      , createDir =
+          λ(x : Text) →
+            < Call :
+                { arguments : List Text
+                , environment : Optional (List { value : Text, var : Text })
+                , procDir : Optional Text
+                , program : Text
+                }
+            | CopyFile : { dest : Text, src : Text }
+            | CreateDirectory : { dir : Text }
+            | MakeExecutable : { file : Text }
+            | Patch : { patchContents : Text }
+            | Symlink : { linkName : Text, tgt : Text }
+            | SymlinkBinary : { file : Text }
+            | SymlinkManpage : { file : Text, section : Natural }
+            | Write : { contents : Text, file : Text }
+            >.CreateDirectory
+              { dir = x }
+      , defaultBuild =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [ "-j${Natural/show cfg.cpus}" ]
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_LIBRARY_PATH"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    merge
+                      { AIX = "make"
+                      , Android = "make"
+                      , Darwin = "make"
+                      , Dragonfly = "gmake"
+                      , FreeBSD = "gmake"
+                      , Haiku = "make"
+                      , Hurd = "make"
+                      , IOS = "make"
+                      , Linux = "make"
+                      , NetBSD = "gmake"
+                      , NoOs = "make"
+                      , OpenBSD = "gmake"
+                      , Redox = "make"
+                      , Solaris = "gmake"
+                      , Windows = "make"
+                      }
+                      cfg.buildOS
+                }
+            ]
+      , defaultCall =
+        { arguments = [] : List Text
+        , environment = None (List { value : Text, var : Text })
+        , procDir = None Text
+        }
+      , defaultConfigure =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ "configure" ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      ( merge
+                          { None = [ "--prefix=${cfg.installDir}" ]
+                          , Some =
+                              λ(x : Text) → [ "--prefix=${cfg.installDir}", x ]
+                          }
+                          ( merge
+                              { None = None Text
+                              , Some =
+                                  λ ( _
+                                    : { abi :
+                                          Optional
+                                            < GNU
+                                            | GNUabi64
+                                            | GNUeabi
+                                            | GNUeabihf
+                                            | GNUspe
+                                            | MinGw
+                                            >
+                                      , arch :
+                                          < AArch
+                                          | Alpha
+                                          | Arm
+                                          | HPPA
+                                          | HPPA64
+                                          | M68k
+                                          | Mips
+                                          | Mips64
+                                          | Mips64El
+                                          | MipsEl
+                                          | MipsIsa32r6
+                                          | MipsIsa32r6El
+                                          | MipsIsa64r6
+                                          | MipsIsa64r6El
+                                          | PowerPC
+                                          | PowerPC64
+                                          | PowerPC64le
+                                          | RISCV64
+                                          | S390x
+                                          | SH4
+                                          | Sparc64
+                                          | X64
+                                          | X86
+                                          >
+                                      , manufacturer :
+                                          Optional
+                                            < Apple | IBM | PC | Unknown >
+                                      , os :
+                                          < AIX
+                                          | Android
+                                          | Darwin
+                                          | Dragonfly
+                                          | FreeBSD
+                                          | Haiku
+                                          | Hurd
+                                          | IOS
+                                          | Linux
+                                          | NetBSD
+                                          | NoOs
+                                          | OpenBSD
+                                          | Redox
+                                          | Solaris
+                                          | Windows
+                                          >
+                                      }
+                                    ) →
+                                    Some
+                                      "--host=${merge
+                                                  { AArch = "aarch64"
+                                                  , Alpha = "alpha"
+                                                  , Arm = "arm"
+                                                  , HPPA = "hppa"
+                                                  , HPPA64 = "hppa64"
+                                                  , M68k = "m68k"
+                                                  , Mips = "mips"
+                                                  , Mips64 = "mips64"
+                                                  , Mips64El = "mips64el"
+                                                  , MipsEl = "mipsel"
+                                                  , MipsIsa32r6 = "mipsisa32r6"
+                                                  , MipsIsa32r6El =
+                                                      "mipsisa32r6el"
+                                                  , MipsIsa64r6 = "mipsisa64r6"
+                                                  , MipsIsa64r6El =
+                                                      "mipsisa64r6el"
+                                                  , PowerPC = "powerpc"
+                                                  , PowerPC64 = "powerpc64"
+                                                  , PowerPC64le = "powerpc64le"
+                                                  , RISCV64 = "riscv64"
+                                                  , S390x = "s390x"
+                                                  , SH4 = "sh4"
+                                                  , Sparc64 = "sparc64"
+                                                  , X64 = "x86_64"
+                                                  , X86 = "i686"
+                                                  }
+                                                  _.arch}-${merge
+                                                              { AIX = "aix"
+                                                              , Android =
+                                                                  "android"
+                                                              , Darwin =
+                                                                  "darwin"
+                                                              , Dragonfly =
+                                                                  "dragonfly"
+                                                              , FreeBSD =
+                                                                  "freebsd"
+                                                              , Haiku = "haiku"
+                                                              , Hurd = "hurd"
+                                                              , IOS = "darwin"
+                                                              , Linux = "linux"
+                                                              , NetBSD =
+                                                                  "netbsd"
+                                                              , NoOs = "none"
+                                                              , OpenBSD =
+                                                                  "openbsd"
+                                                              , Redox = "redox"
+                                                              , Solaris =
+                                                                  "solaris"
+                                                              , Windows = "w64"
+                                                              }
+                                                              _.os}${merge
+                                                                       { None =
+                                                                           ""
+                                                                       , Some =
+                                                                           λ ( abi
+                                                                             : < GNU
+                                                                               | GNUabi64
+                                                                               | GNUeabi
+                                                                               | GNUeabihf
+                                                                               | GNUspe
+                                                                               | MinGw
+                                                                               >
+                                                                             ) →
+                                                                             "-${merge
+                                                                                   { GNU =
+                                                                                       "gnu"
+                                                                                   , GNUabi64 =
+                                                                                       "gnuabi64"
+                                                                                   , GNUeabi =
+                                                                                       "gnueabi"
+                                                                                   , GNUeabihf =
+                                                                                       "gnueabihf"
+                                                                                   , GNUspe =
+                                                                                       "gnuspe"
+                                                                                   , MinGw =
+                                                                                       "mingw32"
+                                                                                   }
+                                                                                   abi}"
+                                                                       }
+                                                                       _.abi}"
+                              }
+                              cfg.targetTriple
+                          )
+                      )
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.includeDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-I${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${if cfg.static then " -static" else ""}"
+                          , var = "CPPFLAGS"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , if    cfg.static
+                          then  { value =
+                                    "${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${_@1}:${_}"
+                                         )
+                                         ""}/usr/local/lib:/lib:/usr/lib"
+                                , var = "LIBRARY_PATH"
+                                }
+                          else  { value =
+                                    merge
+                                      { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                      ( List/fold
+                                          Text
+                                          cfg.linkDirs
+                                          < Empty | NonEmpty : Text >
+                                          ( λ(_ : Text) →
+                                            λ(_ : < Empty | NonEmpty : Text >) →
+                                              merge
+                                                { Empty =
+                                                    < Empty
+                                                    | NonEmpty : Text
+                                                    >.NonEmpty
+                                                      _@1
+                                                , NonEmpty =
+                                                    λ(_ : Text) →
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        "${_@2}:${_}"
+                                                }
+                                                _
+                                          )
+                                          < Empty | NonEmpty : Text >.Empty
+                                      )
+                                , var = "LD_LIBRARY_PATH"
+                                }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_RUN_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./configure"
+                }
+            ]
+      , defaultCpus =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            cfg.cpus
+      , defaultEnv = None (List { value : Text, var : Text })
+      , defaultInstall =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [ "install" ]
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_LIBRARY_PATH"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program =
+                    merge
+                      { AIX = "make"
+                      , Android = "make"
+                      , Darwin = "make"
+                      , Dragonfly = "gmake"
+                      , FreeBSD = "gmake"
+                      , Haiku = "make"
+                      , Hurd = "make"
+                      , IOS = "make"
+                      , Linux = "make"
+                      , NetBSD = "gmake"
+                      , NoOs = "make"
+                      , OpenBSD = "gmake"
+                      , Redox = "make"
+                      , Solaris = "gmake"
+                      , Windows = "make"
+                      }
+                      cfg.buildOS
+                }
+            ]
+      , defaultPackage =
+        { buildCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments = [ "-j${Natural/show cfg.cpus}" ]
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_LIBRARY_PATH"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      merge
+                        { AIX = "make"
+                        , Android = "make"
+                        , Darwin = "make"
+                        , Dragonfly = "gmake"
+                        , FreeBSD = "gmake"
+                        , Haiku = "make"
+                        , Hurd = "make"
+                        , IOS = "make"
+                        , Linux = "make"
+                        , NetBSD = "gmake"
+                        , NoOs = "make"
+                        , OpenBSD = "gmake"
+                        , Redox = "make"
+                        , Solaris = "gmake"
+                        , Windows = "make"
+                        }
+                        cfg.buildOS
+                  }
+              ]
+        , configureCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments =
+                      ( if    merge
+                                { AIX = False
+                                , Android = False
+                                , Darwin = True
+                                , Dragonfly = False
+                                , FreeBSD = False
+                                , Haiku = False
+                                , Hurd = False
+                                , IOS = False
+                                , Linux = False
+                                , NetBSD = False
+                                , NoOs = False
+                                , OpenBSD = False
+                                , Redox = False
+                                , Solaris = False
+                                , Windows = False
+                                }
+                                cfg.buildOS
+                        then  λ(x : List Text) → [ "configure" ] # x
+                        else  λ(x : List Text) → x
+                      )
+                        ( merge
+                            { None = [ "--prefix=${cfg.installDir}" ]
+                            , Some =
+                                λ(x : Text) →
+                                  [ "--prefix=${cfg.installDir}", x ]
+                            }
+                            ( merge
+                                { None = None Text
+                                , Some =
+                                    λ ( _
+                                      : { abi :
+                                            Optional
+                                              < GNU
+                                              | GNUabi64
+                                              | GNUeabi
+                                              | GNUeabihf
+                                              | GNUspe
+                                              | MinGw
+                                              >
+                                        , arch :
+                                            < AArch
+                                            | Alpha
+                                            | Arm
+                                            | HPPA
+                                            | HPPA64
+                                            | M68k
+                                            | Mips
+                                            | Mips64
+                                            | Mips64El
+                                            | MipsEl
+                                            | MipsIsa32r6
+                                            | MipsIsa32r6El
+                                            | MipsIsa64r6
+                                            | MipsIsa64r6El
+                                            | PowerPC
+                                            | PowerPC64
+                                            | PowerPC64le
+                                            | RISCV64
+                                            | S390x
+                                            | SH4
+                                            | Sparc64
+                                            | X64
+                                            | X86
+                                            >
+                                        , manufacturer :
+                                            Optional
+                                              < Apple | IBM | PC | Unknown >
+                                        , os :
+                                            < AIX
+                                            | Android
+                                            | Darwin
+                                            | Dragonfly
+                                            | FreeBSD
+                                            | Haiku
+                                            | Hurd
+                                            | IOS
+                                            | Linux
+                                            | NetBSD
+                                            | NoOs
+                                            | OpenBSD
+                                            | Redox
+                                            | Solaris
+                                            | Windows
+                                            >
+                                        }
+                                      ) →
+                                      Some
+                                        "--host=${merge
+                                                    { AArch = "aarch64"
+                                                    , Alpha = "alpha"
+                                                    , Arm = "arm"
+                                                    , HPPA = "hppa"
+                                                    , HPPA64 = "hppa64"
+                                                    , M68k = "m68k"
+                                                    , Mips = "mips"
+                                                    , Mips64 = "mips64"
+                                                    , Mips64El = "mips64el"
+                                                    , MipsEl = "mipsel"
+                                                    , MipsIsa32r6 =
+                                                        "mipsisa32r6"
+                                                    , MipsIsa32r6El =
+                                                        "mipsisa32r6el"
+                                                    , MipsIsa64r6 =
+                                                        "mipsisa64r6"
+                                                    , MipsIsa64r6El =
+                                                        "mipsisa64r6el"
+                                                    , PowerPC = "powerpc"
+                                                    , PowerPC64 = "powerpc64"
+                                                    , PowerPC64le =
+                                                        "powerpc64le"
+                                                    , RISCV64 = "riscv64"
+                                                    , S390x = "s390x"
+                                                    , SH4 = "sh4"
+                                                    , Sparc64 = "sparc64"
+                                                    , X64 = "x86_64"
+                                                    , X86 = "i686"
+                                                    }
+                                                    _.arch}-${merge
+                                                                { AIX = "aix"
+                                                                , Android =
+                                                                    "android"
+                                                                , Darwin =
+                                                                    "darwin"
+                                                                , Dragonfly =
+                                                                    "dragonfly"
+                                                                , FreeBSD =
+                                                                    "freebsd"
+                                                                , Haiku =
+                                                                    "haiku"
+                                                                , Hurd = "hurd"
+                                                                , IOS = "darwin"
+                                                                , Linux =
+                                                                    "linux"
+                                                                , NetBSD =
+                                                                    "netbsd"
+                                                                , NoOs = "none"
+                                                                , OpenBSD =
+                                                                    "openbsd"
+                                                                , Redox =
+                                                                    "redox"
+                                                                , Solaris =
+                                                                    "solaris"
+                                                                , Windows =
+                                                                    "w64"
+                                                                }
+                                                                _.os}${merge
+                                                                         { None =
+                                                                             ""
+                                                                         , Some =
+                                                                             λ ( abi
+                                                                               : < GNU
+                                                                                 | GNUabi64
+                                                                                 | GNUeabi
+                                                                                 | GNUeabihf
+                                                                                 | GNUspe
+                                                                                 | MinGw
+                                                                                 >
+                                                                               ) →
+                                                                               "-${merge
+                                                                                     { GNU =
+                                                                                         "gnu"
+                                                                                     , GNUabi64 =
+                                                                                         "gnuabi64"
+                                                                                     , GNUeabi =
+                                                                                         "gnueabi"
+                                                                                     , GNUeabihf =
+                                                                                         "gnueabihf"
+                                                                                     , GNUspe =
+                                                                                         "gnuspe"
+                                                                                     , MinGw =
+                                                                                         "mingw32"
+                                                                                     }
+                                                                                     abi}"
+                                                                         }
+                                                                         _.abi}"
+                                }
+                                cfg.targetTriple
+                            )
+                        )
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.includeDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-I${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-I${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${if cfg.static then " -static" else ""}"
+                            , var = "CPPFLAGS"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , if    cfg.static
+                            then  { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/lib:/lib:/usr/lib"
+                                  , var = "LIBRARY_PATH"
+                                  }
+                            else  { value =
+                                      merge
+                                        { Empty = ""
+                                        , NonEmpty = λ(_ : Text) → _
+                                        }
+                                        ( List/fold
+                                            Text
+                                            cfg.linkDirs
+                                            < Empty | NonEmpty : Text >
+                                            ( λ(_ : Text) →
+                                              λ ( _
+                                                : < Empty | NonEmpty : Text >
+                                                ) →
+                                                merge
+                                                  { Empty =
+                                                      < Empty
+                                                      | NonEmpty : Text
+                                                      >.NonEmpty
+                                                        _@1
+                                                  , NonEmpty =
+                                                      λ(_ : Text) →
+                                                        < Empty
+                                                        | NonEmpty : Text
+                                                        >.NonEmpty
+                                                          "${_@2}:${_}"
+                                                  }
+                                                  _
+                                            )
+                                            < Empty | NonEmpty : Text >.Empty
+                                        )
+                                  , var = "LD_LIBRARY_PATH"
+                                  }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_RUN_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  "sh"
+                      else  "./configure"
+                  }
+              ]
+        , installCommand =
+            λ ( cfg
+              : { binDirs : List Text
+                , buildArch :
+                    < AArch
+                    | Alpha
+                    | Arm
+                    | HPPA
+                    | HPPA64
+                    | M68k
+                    | Mips
+                    | Mips64
+                    | Mips64El
+                    | MipsEl
+                    | MipsIsa32r6
+                    | MipsIsa32r6El
+                    | MipsIsa64r6
+                    | MipsIsa64r6El
+                    | PowerPC
+                    | PowerPC64
+                    | PowerPC64le
+                    | RISCV64
+                    | S390x
+                    | SH4
+                    | Sparc64
+                    | X64
+                    | X86
+                    >
+                , buildOS :
+                    < AIX
+                    | Android
+                    | Darwin
+                    | Dragonfly
+                    | FreeBSD
+                    | Haiku
+                    | Hurd
+                    | IOS
+                    | Linux
+                    | NetBSD
+                    | NoOs
+                    | OpenBSD
+                    | Redox
+                    | Solaris
+                    | Windows
+                    >
+                , cpus : Natural
+                , currentDir : Text
+                , includeDirs : List Text
+                , installDir : Text
+                , isCross : Bool
+                , linkDirs : List Text
+                , preloadLibs : List Text
+                , shareDirs : List Text
+                , static : Bool
+                , targetTriple :
+                    Optional
+                      { abi :
+                          Optional
+                            < GNU
+                            | GNUabi64
+                            | GNUeabi
+                            | GNUeabihf
+                            | GNUspe
+                            | MinGw
+                            >
+                      , arch :
+                          < AArch
+                          | Alpha
+                          | Arm
+                          | HPPA
+                          | HPPA64
+                          | M68k
+                          | Mips
+                          | Mips64
+                          | Mips64El
+                          | MipsEl
+                          | MipsIsa32r6
+                          | MipsIsa32r6El
+                          | MipsIsa64r6
+                          | MipsIsa64r6El
+                          | PowerPC
+                          | PowerPC64
+                          | PowerPC64le
+                          | RISCV64
+                          | S390x
+                          | SH4
+                          | Sparc64
+                          | X64
+                          | X86
+                          >
+                      , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                      , os :
+                          < AIX
+                          | Android
+                          | Darwin
+                          | Dragonfly
+                          | FreeBSD
+                          | Haiku
+                          | Hurd
+                          | IOS
+                          | Linux
+                          | NetBSD
+                          | NoOs
+                          | OpenBSD
+                          | Redox
+                          | Solaris
+                          | Windows
+                          >
+                      }
+                }
+              ) →
+              [ < Call :
+                    { arguments : List Text
+                    , environment : Optional (List { value : Text, var : Text })
+                    , procDir : Optional Text
+                    , program : Text
+                    }
+                | CopyFile : { dest : Text, src : Text }
+                | CreateDirectory : { dir : Text }
+                | MakeExecutable : { file : Text }
+                | Patch : { patchContents : Text }
+                | Symlink : { linkName : Text, tgt : Text }
+                | SymlinkBinary : { file : Text }
+                | SymlinkManpage : { file : Text, section : Natural }
+                | Write : { contents : Text, file : Text }
+                >.Call
+                  { arguments = [ "install" ]
+                  , environment = Some
+                      (   ( if    merge
+                                    { AIX = True
+                                    , Android = True
+                                    , Darwin = True
+                                    , Dragonfly = True
+                                    , FreeBSD = True
+                                    , Haiku = False
+                                    , Hurd = True
+                                    , IOS = True
+                                    , Linux = True
+                                    , NetBSD = True
+                                    , NoOs = False
+                                    , OpenBSD = True
+                                    , Redox = False
+                                    , Solaris = True
+                                    , Windows = False
+                                    }
+                                    cfg.buildOS
+                            then  [ { value =
+                                        "${List/fold
+                                             Text
+                                             cfg.binDirs
+                                             Text
+                                             ( λ(_ : Text) →
+                                               λ(_ : Text) →
+                                                 "${_@1}:${_}"
+                                             )
+                                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                    , var = "PATH"
+                                    }
+                                  ]
+                            else  [] : List { value : Text, var : Text }
+                          )
+                        # [ { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      (cfg.shareDirs # cfg.linkDirs)
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/pkgconfig"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/pkgconfig:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PKG_CONFIG_PATH"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@1}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/"
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}/site_perl/5.30.2/${merge
+                                                                                 { AArch =
+                                                                                     "aarch64"
+                                                                                 , Alpha =
+                                                                                     "alpha"
+                                                                                 , Arm =
+                                                                                     "arm"
+                                                                                 , HPPA =
+                                                                                     "hppa"
+                                                                                 , HPPA64 =
+                                                                                     "hppa64"
+                                                                                 , M68k =
+                                                                                     "m68k"
+                                                                                 , Mips =
+                                                                                     "mips"
+                                                                                 , Mips64 =
+                                                                                     "mips64"
+                                                                                 , Mips64El =
+                                                                                     "mips64el"
+                                                                                 , MipsEl =
+                                                                                     "mipsel"
+                                                                                 , MipsIsa32r6 =
+                                                                                     "mipsisa32r6"
+                                                                                 , MipsIsa32r6El =
+                                                                                     "mipsisa32r6el"
+                                                                                 , MipsIsa64r6 =
+                                                                                     "mipsisa64r6"
+                                                                                 , MipsIsa64r6El =
+                                                                                     "mipsisa64r6el"
+                                                                                 , PowerPC =
+                                                                                     "powerpc"
+                                                                                 , PowerPC64 =
+                                                                                     "powerpc64"
+                                                                                 , PowerPC64le =
+                                                                                     "powerpc64le"
+                                                                                 , RISCV64 =
+                                                                                     "riscv64"
+                                                                                 , S390x =
+                                                                                     "s390x"
+                                                                                 , SH4 =
+                                                                                     "sh4"
+                                                                                 , Sparc64 =
+                                                                                     "sparc64"
+                                                                                 , X64 =
+                                                                                     "x86_64"
+                                                                                 , X86 =
+                                                                                     "i686"
+                                                                                 }
+                                                                                 cfg.buildArch}-${merge
+                                                                                                    { AIX =
+                                                                                                        "aix"
+                                                                                                    , Android =
+                                                                                                        "android"
+                                                                                                    , Darwin =
+                                                                                                        "darwin"
+                                                                                                    , Dragonfly =
+                                                                                                        "dragonfly"
+                                                                                                    , FreeBSD =
+                                                                                                        "freebsd"
+                                                                                                    , Haiku =
+                                                                                                        "haiku"
+                                                                                                    , Hurd =
+                                                                                                        "hurd"
+                                                                                                    , IOS =
+                                                                                                        "darwin"
+                                                                                                    , Linux =
+                                                                                                        "linux"
+                                                                                                    , NetBSD =
+                                                                                                        "netbsd"
+                                                                                                    , NoOs =
+                                                                                                        "none"
+                                                                                                    , OpenBSD =
+                                                                                                        "openbsd"
+                                                                                                    , Redox =
+                                                                                                        "redox"
+                                                                                                    , Solaris =
+                                                                                                        "solaris"
+                                                                                                    , Windows =
+                                                                                                        "w64"
+                                                                                                    }
+                                                                                                    cfg.buildOS}/:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "PERL5LIB"
+                            }
+                          , { value =
+                                merge
+                                  { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                  ( List/fold
+                                      Text
+                                      cfg.linkDirs
+                                      < Empty | NonEmpty : Text >
+                                      ( λ(_ : Text) →
+                                        λ(_ : < Empty | NonEmpty : Text >) →
+                                          merge
+                                            { Empty =
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  _@1
+                                            , NonEmpty =
+                                                λ(_ : Text) →
+                                                  < Empty
+                                                  | NonEmpty : Text
+                                                  >.NonEmpty
+                                                    "${_@2}:${_}"
+                                            }
+                                            _
+                                      )
+                                      < Empty | NonEmpty : Text >.Empty
+                                  )
+                            , var = "LD_LIBRARY_PATH"
+                            }
+                          , { value =
+                                "${merge
+                                     { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                     ( List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         < Empty | NonEmpty : Text >
+                                         ( λ(_ : Text) →
+                                           λ(_ : < Empty | NonEmpty : Text >) →
+                                             merge
+                                               { Empty =
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@1}"
+                                               , NonEmpty =
+                                                   λ(_ : Text) →
+                                                     < Empty
+                                                     | NonEmpty : Text
+                                                     >.NonEmpty
+                                                       "-L${_@2} ${_}"
+                                               }
+                                               _
+                                         )
+                                         < Empty | NonEmpty : Text >.Empty
+                                     )}${List/fold
+                                           Text
+                                           cfg.linkDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${if    merge
+                                                          { AIX = False
+                                                          , Android = False
+                                                          , Darwin = True
+                                                          , Dragonfly = False
+                                                          , FreeBSD = False
+                                                          , Haiku = False
+                                                          , Hurd = False
+                                                          , IOS = False
+                                                          , Linux = False
+                                                          , NetBSD = False
+                                                          , NoOs = False
+                                                          , OpenBSD = False
+                                                          , Redox = False
+                                                          , Solaris = False
+                                                          , Windows = False
+                                                          }
+                                                          cfg.buildOS
+                                                  then  ""
+                                                  else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                           )
+                                           ""}"
+                            , var = "LDFLAGS"
+                            }
+                          ]
+                      )
+                  , procDir = None Text
+                  , program =
+                      merge
+                        { AIX = "make"
+                        , Android = "make"
+                        , Darwin = "make"
+                        , Dragonfly = "gmake"
+                        , FreeBSD = "gmake"
+                        , Haiku = "make"
+                        , Hurd = "make"
+                        , IOS = "make"
+                        , Linux = "make"
+                        , NetBSD = "gmake"
+                        , NoOs = "make"
+                        , OpenBSD = "gmake"
+                        , Redox = "make"
+                        , Solaris = "gmake"
+                        , Windows = "make"
+                        }
+                        cfg.buildOS
+                  }
+              ]
+        , pkgBuildDeps =
+            [] : List
+                   { bound :
+                       < Lower : { lower : List Natural }
+                       | LowerUpper :
+                           { lower : List Natural, upper : List Natural }
+                       | NoBound
+                       | Upper : { upper : List Natural }
+                       >
+                   , name : Text
+                   }
+        , pkgDeps =
+            [] : List
+                   { bound :
+                       < Lower : { lower : List Natural }
+                       | LowerUpper :
+                           { lower : List Natural, upper : List Natural }
+                       | NoBound
+                       | Upper : { upper : List Natural }
+                       >
+                   , name : Text
+                   }
+        }
+      , defaultPath =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            if    merge
+                    { AIX = True
+                    , Android = True
+                    , Darwin = True
+                    , Dragonfly = True
+                    , FreeBSD = True
+                    , Haiku = False
+                    , Hurd = True
+                    , IOS = True
+                    , Linux = True
+                    , NetBSD = True
+                    , NoOs = False
+                    , OpenBSD = True
+                    , Redox = False
+                    , Solaris = True
+                    , Windows = False
+                    }
+                    cfg.buildOS
+            then  [ { value =
+                        "${List/fold
+                             Text
+                             cfg.binDirs
+                             Text
+                             (λ(_ : Text) → λ(_ : Text) → "${_@1}:${_}")
+                             ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                    , var = "PATH"
+                    }
+                  ]
+            else  [] : List { value : Text, var : Text }
+      , doNothing =
+          λ ( _
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [] : List
+                   < Call :
+                       { arguments : List Text
+                       , environment :
+                           Optional (List { value : Text, var : Text })
+                       , procDir : Optional Text
+                       , program : Text
+                       }
+                   | CopyFile : { dest : Text, src : Text }
+                   | CreateDirectory : { dir : Text }
+                   | MakeExecutable : { file : Text }
+                   | Patch : { patchContents : Text }
+                   | Symlink : { linkName : Text, tgt : Text }
+                   | SymlinkBinary : { file : Text }
+                   | SymlinkManpage : { file : Text, section : Natural }
+                   | Write : { contents : Text, file : Text }
+                   >
+      , fullVersion =
+          λ(x : { patch : Natural, version : List Natural }) →
+            x.version # [ x.patch ]
+      , generalBuild =
+          λ ( cpus
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              } →
+                Natural
+            ) →
+          λ(envs : List { value : Text, var : Text }) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [ "-j${Natural/show (cpus cfg)}" ]
+                , environment = Some envs
+                , procDir = None Text
+                , program =
+                    merge
+                      { AIX = "make"
+                      , Android = "make"
+                      , Darwin = "make"
+                      , Dragonfly = "gmake"
+                      , FreeBSD = "gmake"
+                      , Haiku = "make"
+                      , Hurd = "make"
+                      , IOS = "make"
+                      , Linux = "make"
+                      , NetBSD = "gmake"
+                      , NoOs = "make"
+                      , OpenBSD = "gmake"
+                      , Redox = "make"
+                      , Solaris = "gmake"
+                      , Windows = "make"
+                      }
+                      cfg.buildOS
+                }
+            ]
+      , generalConfigure =
+          λ ( envVars
+            : List Text →
+              { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              } →
+                Optional (List { value : Text, var : Text })
+            ) →
+          λ(filename : Text) →
+          λ(linkLibs : List Text) →
+          λ(extraFlags : List Text) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                    ( if    merge
+                              { AIX = False
+                              , Android = False
+                              , Darwin = True
+                              , Dragonfly = False
+                              , FreeBSD = False
+                              , Haiku = False
+                              , Hurd = False
+                              , IOS = False
+                              , Linux = False
+                              , NetBSD = False
+                              , NoOs = False
+                              , OpenBSD = False
+                              , Redox = False
+                              , Solaris = False
+                              , Windows = False
+                              }
+                              cfg.buildOS
+                      then  λ(x : List Text) → [ filename ] # x
+                      else  λ(x : List Text) → x
+                    )
+                      (   merge
+                            { None = [ "--prefix=${cfg.installDir}" ]
+                            , Some =
+                                λ(x : Text) →
+                                  [ "--prefix=${cfg.installDir}", x ]
+                            }
+                            ( merge
+                                { None = None Text
+                                , Some =
+                                    λ ( _
+                                      : { abi :
+                                            Optional
+                                              < GNU
+                                              | GNUabi64
+                                              | GNUeabi
+                                              | GNUeabihf
+                                              | GNUspe
+                                              | MinGw
+                                              >
+                                        , arch :
+                                            < AArch
+                                            | Alpha
+                                            | Arm
+                                            | HPPA
+                                            | HPPA64
+                                            | M68k
+                                            | Mips
+                                            | Mips64
+                                            | Mips64El
+                                            | MipsEl
+                                            | MipsIsa32r6
+                                            | MipsIsa32r6El
+                                            | MipsIsa64r6
+                                            | MipsIsa64r6El
+                                            | PowerPC
+                                            | PowerPC64
+                                            | PowerPC64le
+                                            | RISCV64
+                                            | S390x
+                                            | SH4
+                                            | Sparc64
+                                            | X64
+                                            | X86
+                                            >
+                                        , manufacturer :
+                                            Optional
+                                              < Apple | IBM | PC | Unknown >
+                                        , os :
+                                            < AIX
+                                            | Android
+                                            | Darwin
+                                            | Dragonfly
+                                            | FreeBSD
+                                            | Haiku
+                                            | Hurd
+                                            | IOS
+                                            | Linux
+                                            | NetBSD
+                                            | NoOs
+                                            | OpenBSD
+                                            | Redox
+                                            | Solaris
+                                            | Windows
+                                            >
+                                        }
+                                      ) →
+                                      Some
+                                        "--host=${merge
+                                                    { AArch = "aarch64"
+                                                    , Alpha = "alpha"
+                                                    , Arm = "arm"
+                                                    , HPPA = "hppa"
+                                                    , HPPA64 = "hppa64"
+                                                    , M68k = "m68k"
+                                                    , Mips = "mips"
+                                                    , Mips64 = "mips64"
+                                                    , Mips64El = "mips64el"
+                                                    , MipsEl = "mipsel"
+                                                    , MipsIsa32r6 =
+                                                        "mipsisa32r6"
+                                                    , MipsIsa32r6El =
+                                                        "mipsisa32r6el"
+                                                    , MipsIsa64r6 =
+                                                        "mipsisa64r6"
+                                                    , MipsIsa64r6El =
+                                                        "mipsisa64r6el"
+                                                    , PowerPC = "powerpc"
+                                                    , PowerPC64 = "powerpc64"
+                                                    , PowerPC64le =
+                                                        "powerpc64le"
+                                                    , RISCV64 = "riscv64"
+                                                    , S390x = "s390x"
+                                                    , SH4 = "sh4"
+                                                    , Sparc64 = "sparc64"
+                                                    , X64 = "x86_64"
+                                                    , X86 = "i686"
+                                                    }
+                                                    _.arch}-${merge
+                                                                { AIX = "aix"
+                                                                , Android =
+                                                                    "android"
+                                                                , Darwin =
+                                                                    "darwin"
+                                                                , Dragonfly =
+                                                                    "dragonfly"
+                                                                , FreeBSD =
+                                                                    "freebsd"
+                                                                , Haiku =
+                                                                    "haiku"
+                                                                , Hurd = "hurd"
+                                                                , IOS = "darwin"
+                                                                , Linux =
+                                                                    "linux"
+                                                                , NetBSD =
+                                                                    "netbsd"
+                                                                , NoOs = "none"
+                                                                , OpenBSD =
+                                                                    "openbsd"
+                                                                , Redox =
+                                                                    "redox"
+                                                                , Solaris =
+                                                                    "solaris"
+                                                                , Windows =
+                                                                    "w64"
+                                                                }
+                                                                _.os}${merge
+                                                                         { None =
+                                                                             ""
+                                                                         , Some =
+                                                                             λ ( abi
+                                                                               : < GNU
+                                                                                 | GNUabi64
+                                                                                 | GNUeabi
+                                                                                 | GNUeabihf
+                                                                                 | GNUspe
+                                                                                 | MinGw
+                                                                                 >
+                                                                               ) →
+                                                                               "-${merge
+                                                                                     { GNU =
+                                                                                         "gnu"
+                                                                                     , GNUabi64 =
+                                                                                         "gnuabi64"
+                                                                                     , GNUeabi =
+                                                                                         "gnueabi"
+                                                                                     , GNUeabihf =
+                                                                                         "gnueabihf"
+                                                                                     , GNUspe =
+                                                                                         "gnuspe"
+                                                                                     , MinGw =
+                                                                                         "mingw32"
+                                                                                     }
+                                                                                     abi}"
+                                                                         }
+                                                                         _.abi}"
+                                }
+                                cfg.targetTriple
+                            )
+                        # extraFlags
+                      )
+                , environment = envVars linkLibs cfg
+                , procDir = None Text
+                , program =
+                    if    merge
+                            { AIX = False
+                            , Android = False
+                            , Darwin = True
+                            , Dragonfly = False
+                            , FreeBSD = False
+                            , Haiku = False
+                            , Hurd = False
+                            , IOS = False
+                            , Linux = False
+                            , NetBSD = False
+                            , NoOs = False
+                            , OpenBSD = False
+                            , Redox = False
+                            , Solaris = False
+                            , Windows = False
+                            }
+                            cfg.buildOS
+                    then  "sh"
+                    else  "./${filename}"
+                }
+            ]
+      , installPrefix =
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments =
+                  [ "prefix=${cfg.installDir}"
+                  , "PREFIX=${cfg.installDir}"
+                  , "install"
+                  ]
+                , environment = Some
+                    (   ( if    merge
+                                  { AIX = True
+                                  , Android = True
+                                  , Darwin = True
+                                  , Dragonfly = True
+                                  , FreeBSD = True
+                                  , Haiku = False
+                                  , Hurd = True
+                                  , IOS = True
+                                  , Linux = True
+                                  , NetBSD = True
+                                  , NoOs = False
+                                  , OpenBSD = True
+                                  , Redox = False
+                                  , Solaris = True
+                                  , Windows = False
+                                  }
+                                  cfg.buildOS
+                          then  [ { value =
+                                      "${List/fold
+                                           Text
+                                           cfg.binDirs
+                                           Text
+                                           ( λ(_ : Text) →
+                                             λ(_ : Text) →
+                                               "${_@1}:${_}"
+                                           )
+                                           ""}/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin"
+                                  , var = "PATH"
+                                  }
+                                ]
+                          else  [] : List { value : Text, var : Text }
+                        )
+                      # [ { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    (cfg.shareDirs # cfg.linkDirs)
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/pkgconfig"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/pkgconfig:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PKG_CONFIG_PATH"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                "${_@1}/site_perl/5.30.2/${merge
+                                                                             { AArch =
+                                                                                 "aarch64"
+                                                                             , Alpha =
+                                                                                 "alpha"
+                                                                             , Arm =
+                                                                                 "arm"
+                                                                             , HPPA =
+                                                                                 "hppa"
+                                                                             , HPPA64 =
+                                                                                 "hppa64"
+                                                                             , M68k =
+                                                                                 "m68k"
+                                                                             , Mips =
+                                                                                 "mips"
+                                                                             , Mips64 =
+                                                                                 "mips64"
+                                                                             , Mips64El =
+                                                                                 "mips64el"
+                                                                             , MipsEl =
+                                                                                 "mipsel"
+                                                                             , MipsIsa32r6 =
+                                                                                 "mipsisa32r6"
+                                                                             , MipsIsa32r6El =
+                                                                                 "mipsisa32r6el"
+                                                                             , MipsIsa64r6 =
+                                                                                 "mipsisa64r6"
+                                                                             , MipsIsa64r6El =
+                                                                                 "mipsisa64r6el"
+                                                                             , PowerPC =
+                                                                                 "powerpc"
+                                                                             , PowerPC64 =
+                                                                                 "powerpc64"
+                                                                             , PowerPC64le =
+                                                                                 "powerpc64le"
+                                                                             , RISCV64 =
+                                                                                 "riscv64"
+                                                                             , S390x =
+                                                                                 "s390x"
+                                                                             , SH4 =
+                                                                                 "sh4"
+                                                                             , Sparc64 =
+                                                                                 "sparc64"
+                                                                             , X64 =
+                                                                                 "x86_64"
+                                                                             , X86 =
+                                                                                 "i686"
+                                                                             }
+                                                                             cfg.buildArch}-${merge
+                                                                                                { AIX =
+                                                                                                    "aix"
+                                                                                                , Android =
+                                                                                                    "android"
+                                                                                                , Darwin =
+                                                                                                    "darwin"
+                                                                                                , Dragonfly =
+                                                                                                    "dragonfly"
+                                                                                                , FreeBSD =
+                                                                                                    "freebsd"
+                                                                                                , Haiku =
+                                                                                                    "haiku"
+                                                                                                , Hurd =
+                                                                                                    "hurd"
+                                                                                                , IOS =
+                                                                                                    "darwin"
+                                                                                                , Linux =
+                                                                                                    "linux"
+                                                                                                , NetBSD =
+                                                                                                    "netbsd"
+                                                                                                , NoOs =
+                                                                                                    "none"
+                                                                                                , OpenBSD =
+                                                                                                    "openbsd"
+                                                                                                , Redox =
+                                                                                                    "redox"
+                                                                                                , Solaris =
+                                                                                                    "solaris"
+                                                                                                , Windows =
+                                                                                                    "w64"
+                                                                                                }
+                                                                                                cfg.buildOS}/"
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}/site_perl/5.30.2/${merge
+                                                                               { AArch =
+                                                                                   "aarch64"
+                                                                               , Alpha =
+                                                                                   "alpha"
+                                                                               , Arm =
+                                                                                   "arm"
+                                                                               , HPPA =
+                                                                                   "hppa"
+                                                                               , HPPA64 =
+                                                                                   "hppa64"
+                                                                               , M68k =
+                                                                                   "m68k"
+                                                                               , Mips =
+                                                                                   "mips"
+                                                                               , Mips64 =
+                                                                                   "mips64"
+                                                                               , Mips64El =
+                                                                                   "mips64el"
+                                                                               , MipsEl =
+                                                                                   "mipsel"
+                                                                               , MipsIsa32r6 =
+                                                                                   "mipsisa32r6"
+                                                                               , MipsIsa32r6El =
+                                                                                   "mipsisa32r6el"
+                                                                               , MipsIsa64r6 =
+                                                                                   "mipsisa64r6"
+                                                                               , MipsIsa64r6El =
+                                                                                   "mipsisa64r6el"
+                                                                               , PowerPC =
+                                                                                   "powerpc"
+                                                                               , PowerPC64 =
+                                                                                   "powerpc64"
+                                                                               , PowerPC64le =
+                                                                                   "powerpc64le"
+                                                                               , RISCV64 =
+                                                                                   "riscv64"
+                                                                               , S390x =
+                                                                                   "s390x"
+                                                                               , SH4 =
+                                                                                   "sh4"
+                                                                               , Sparc64 =
+                                                                                   "sparc64"
+                                                                               , X64 =
+                                                                                   "x86_64"
+                                                                               , X86 =
+                                                                                   "i686"
+                                                                               }
+                                                                               cfg.buildArch}-${merge
+                                                                                                  { AIX =
+                                                                                                      "aix"
+                                                                                                  , Android =
+                                                                                                      "android"
+                                                                                                  , Darwin =
+                                                                                                      "darwin"
+                                                                                                  , Dragonfly =
+                                                                                                      "dragonfly"
+                                                                                                  , FreeBSD =
+                                                                                                      "freebsd"
+                                                                                                  , Haiku =
+                                                                                                      "haiku"
+                                                                                                  , Hurd =
+                                                                                                      "hurd"
+                                                                                                  , IOS =
+                                                                                                      "darwin"
+                                                                                                  , Linux =
+                                                                                                      "linux"
+                                                                                                  , NetBSD =
+                                                                                                      "netbsd"
+                                                                                                  , NoOs =
+                                                                                                      "none"
+                                                                                                  , OpenBSD =
+                                                                                                      "openbsd"
+                                                                                                  , Redox =
+                                                                                                      "redox"
+                                                                                                  , Solaris =
+                                                                                                      "solaris"
+                                                                                                  , Windows =
+                                                                                                      "w64"
+                                                                                                  }
+                                                                                                  cfg.buildOS}/:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "PERL5LIB"
+                          }
+                        , { value =
+                              merge
+                                { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                ( List/fold
+                                    Text
+                                    cfg.linkDirs
+                                    < Empty | NonEmpty : Text >
+                                    ( λ(_ : Text) →
+                                      λ(_ : < Empty | NonEmpty : Text >) →
+                                        merge
+                                          { Empty =
+                                              < Empty
+                                              | NonEmpty : Text
+                                              >.NonEmpty
+                                                _@1
+                                          , NonEmpty =
+                                              λ(_ : Text) →
+                                                < Empty
+                                                | NonEmpty : Text
+                                                >.NonEmpty
+                                                  "${_@2}:${_}"
+                                          }
+                                          _
+                                    )
+                                    < Empty | NonEmpty : Text >.Empty
+                                )
+                          , var = "LD_LIBRARY_PATH"
+                          }
+                        , { value =
+                              "${merge
+                                   { Empty = "", NonEmpty = λ(_ : Text) → _ }
+                                   ( List/fold
+                                       Text
+                                       cfg.linkDirs
+                                       < Empty | NonEmpty : Text >
+                                       ( λ(_ : Text) →
+                                         λ(_ : < Empty | NonEmpty : Text >) →
+                                           merge
+                                             { Empty =
+                                                 < Empty
+                                                 | NonEmpty : Text
+                                                 >.NonEmpty
+                                                   "-L${_@1}"
+                                             , NonEmpty =
+                                                 λ(_ : Text) →
+                                                   < Empty
+                                                   | NonEmpty : Text
+                                                   >.NonEmpty
+                                                     "-L${_@2} ${_}"
+                                             }
+                                             _
+                                       )
+                                       < Empty | NonEmpty : Text >.Empty
+                                   )}${List/fold
+                                         Text
+                                         cfg.linkDirs
+                                         Text
+                                         ( λ(_ : Text) →
+                                           λ(_ : Text) →
+                                             "${if    merge
+                                                        { AIX = False
+                                                        , Android = False
+                                                        , Darwin = True
+                                                        , Dragonfly = False
+                                                        , FreeBSD = False
+                                                        , Haiku = False
+                                                        , Hurd = False
+                                                        , IOS = False
+                                                        , Linux = False
+                                                        , NetBSD = False
+                                                        , NoOs = False
+                                                        , OpenBSD = False
+                                                        , Redox = False
+                                                        , Solaris = False
+                                                        , Windows = False
+                                                        }
+                                                        cfg.buildOS
+                                                then  ""
+                                                else  " -Wl,-rpath-link,${_@1}"}${_}"
+                                         )
+                                         ""}"
+                          , var = "LDFLAGS"
+                          }
+                        ]
+                    )
+                , procDir = None Text
+                , program = "make"
+                }
+            ]
+      , installWith =
+          λ(envs : List { value : Text, var : Text }) →
+          λ ( cfg
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                        | Windows
+                        >
+                    }
+              }
+            ) →
+            [ < Call :
+                  { arguments : List Text
+                  , environment : Optional (List { value : Text, var : Text })
+                  , procDir : Optional Text
+                  , program : Text
+                  }
+              | CopyFile : { dest : Text, src : Text }
+              | CreateDirectory : { dir : Text }
+              | MakeExecutable : { file : Text }
+              | Patch : { patchContents : Text }
+              | Symlink : { linkName : Text, tgt : Text }
+              | SymlinkBinary : { file : Text }
+              | SymlinkManpage : { file : Text, section : Natural }
+              | Write : { contents : Text, file : Text }
+              >.Call
+                { arguments = [ "install" ]
+                , environment = Some envs
+                , procDir = None Text
+                , program =
+                    merge
+                      { AIX = "make"
+                      , Android = "make"
+                      , Darwin = "make"
+                      , Dragonfly = "gmake"
+                      , FreeBSD = "gmake"
+                      , Haiku = "make"
+                      , Hurd = "make"
+                      , IOS = "make"
+                      , Linux = "make"
+                      , NetBSD = "gmake"
+                      , NoOs = "make"
+                      , OpenBSD = "gmake"
+                      , Redox = "make"
+                      , Solaris = "gmake"
+                      , Windows = "make"
+                      }
+                      cfg.buildOS
+                }
+            ]
+      , installWithBinaries =
+          λ(bins : List Text) →
+          λ ( installVars
+            : { binDirs : List Text
+              , buildArch :
+                  < AArch
+                  | Alpha
+                  | Arm
+                  | HPPA
+                  | HPPA64
+                  | M68k
+                  | Mips
+                  | Mips64
+                  | Mips64El
+                  | MipsEl
+                  | MipsIsa32r6
+                  | MipsIsa32r6El
+                  | MipsIsa64r6
+                  | MipsIsa64r6El
+                  | PowerPC
+                  | PowerPC64
+                  | PowerPC64le
+                  | RISCV64
+                  | S390x
+                  | SH4
+                  | Sparc64
+                  | X64
+                  | X86
+                  >
+              , buildOS :
+                  < AIX
+                  | Android
+                  | Darwin
+                  | Dragonfly
+                  | FreeBSD
+                  | Haiku
+                  | Hurd
+                  | IOS
+                  | Linux
+                  | NetBSD
+                  | NoOs
+                  | OpenBSD
+                  | Redox
+                  | Solaris
+                  | Windows
+                  >
+              , cpus : Natural
+              , currentDir : Text
+              , includeDirs : List Text
+              , installDir : Text
+              , isCross : Bool
+              , linkDirs : List Text
+              , preloadLibs : List Text
+              , shareDirs : List Text
+              , static : Bool
+              , targetTriple :
+                  Optional
+                    { abi :
+                        Optional
+                          < GNU
+                          | GNUabi64
+                          | GNUeabi
+                          | GNUeabihf
+                          | GNUspe
+                          | MinGw
+                          >
+                    , arch :
+                        < AArch
+                        | Alpha
+                        | Arm
+                        | HPPA
+                        | HPPA64
+                        | M68k
+                        | Mips
+                        | Mips64
+                        | Mips64El
+                        | MipsEl
+                        | MipsIsa32r6
+                        | MipsIsa32r6El
+                        | MipsIsa64r6
+                        | MipsIsa64r6El
+                        | PowerPC
+                        | PowerPC64
+                        | PowerPC64le
+                        | RISCV64
+                        | S390x
+                        | SH4
+                        | Sparc64
+                        | X64
+                        | X86
+                        >
+                    , manufacturer : Optional < Apple | IBM | PC | Unknown >
+                    , os :
+                        < AIX
+                        | Android
+                        | Darwin
+                        | Dragonfly
+                        | FreeBSD
+                        | Haiku
+                        | Hurd
+                        | IOS
+                        | Linux
+                        | NetBSD
+                        | NoOs
+                        | OpenBSD
+                        | Redox
+                        | Solaris
+                      