ngx-export-distribution-0.3.2.0: Build custom libraries for Nginx haskell module
Copyright(c) Alexey Radkov 2021
LicenseBSD-style
Maintaineralexey.radkov@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

NgxExport.Distribution

Description

Quick and dirty build of simple shared libraries and collecting dependencies. This was designed to build custom Haskell handlers for nginx-haskell-module.

Synopsis

Usage and examples

This module allows for building simple shared libraries with Cabal.

Below is a simple example.

File ngx_distribution_test.hs

{-# LANGUAGE TemplateHaskell #-}

module NgxDistributionTest where

import           NgxExport

import           Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy.Char8 as C8L
import           Data.Aeson
import           Data.Maybe

incCnt :: ByteString -> C8L.ByteString
incCnt = C8L.pack . show . succ . fromMaybe (0 :: Int) . decodeStrict
ngxExportYY 'incCnt

File ngx-distribution-test.cabal

name:                       ngx-distribution-test
version:                    0.1.0.0
build-type:                 Custom
cabal-version:              1.24

custom-setup
  setup-depends:            base >= 4.8 && < 5
                          , ngx-export-distribution

library
  default-language:         Haskell2010
  build-depends:            base >= 4.8 && < 5
                          , ngx-export
                          , bytestring
                          , aeson

  ghc-options:             -Wall -O2 -no-keep-hi-files -no-keep-o-files
                           -package=base
                           -package=ngx-export
                           -package=bytestring
                           -package=aeson

All packages listed in build-depends get also wrapped inside options -package in ghc-options: this is important when building them with cabal v2-build and then using inside GHC package environments.

File Setup.hs

import NgxExport.Distribution
main = defaultMain

The configuration step requires that utilities patchelf and hslibdeps were found in the paths of environment variable $PATH.

Building is a bit cumbersome: it expects explicit option --prefix at the configuration step (which will be interpreted as the prefix part of the rpath by utility hslibdeps) and explicit ghc option -o at the build step which is as well used by hslibdeps as the name of the target library.

Building with cabal v1-commands

Let's build the example with commands cabal v1-configure and cabal v1-build.

$ cabal v1-install --only-dependencies
Resolving dependencies...
All the requested packages are already installed:
Use --reinstall if you want to reinstall anyway.
$ cabal v1-configure --prefix=/var/lib/nginx
Resolving dependencies...
[1 of 1] Compiling Main             ( dist/setup/setup.hs, dist/setup/Main.o )
Linking ./dist/setup/setup ...
Configuring ngx-distribution-test-0.1.0.0...
$ cabal v1-build --ghc-options="ngx_distribution_test.hs -o ngx_distribution_test.so -threaded"
[1 of 1] Compiling NgxDistributionTest ( ngx_distribution_test.hs, ngx_distribution_test.o )
Linking ngx_distribution_test.so ...
---> Collecting libraries
'/usr/lib64/libHSrts-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSrts-ghc8.10.5.so'
'/home/lyokha/.cabal/lib/x86_64-linux-ghc-8.10.5/libHSngx-export-1.7.5-JzTEmHewqdC9gGi6rzcAtt-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSngx-export-1.7.5-JzTEmHewqdC9gGi6rzcAtt-ghc8.10.5.so'
'/home/lyokha/.cabal/lib/x86_64-linux-ghc-8.10.5/libHSmonad-loops-0.4.3-8Lx5Hn3pTtO62yOPdPW77x-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSmonad-loops-0.4.3-8Lx5Hn3pTtO62yOPdPW77x-ghc8.10.5.so'
'/home/lyokha/.cabal/lib/x86_64-linux-ghc-8.10.5/libHSasync-2.2.4-ENjuIeC23kaKyMVDRYThP3-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSasync-2.2.4-ENjuIeC23kaKyMVDRYThP3-ghc8.10.5.so'
'/usr/lib64/libHSstm-2.5.0.1-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSstm-2.5.0.1-ghc8.10.5.so'
'/home/lyokha/.cabal/lib/x86_64-linux-ghc-8.10.5/libHSaeson-1.5.6.0-6XeGmWHoO3vJYEUW5PXPgC-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSaeson-1.5.6.0-6XeGmWHoO3vJYEUW5PXPgC-ghc8.10.5.so'

   ...

'/usr/lib64/libHSbase-4.14.2.0-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSbase-4.14.2.0-ghc8.10.5.so'
'/usr/lib64/libHSinteger-gmp-1.0.3.0-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSinteger-gmp-1.0.3.0-ghc8.10.5.so'
'/usr/lib64/libHSghc-prim-0.6.1-ghc8.10.5.so' -> 'x86_64-linux-ghc-8.10.5/libHSghc-prim-0.6.1-ghc8.10.5.so'

---> Patching ngx_distribution_test.so
/var/lib/nginx/x86_64-linux-ghc-8.10.5:/home/lyokha/.cabal/lib/x86_64-linux-ghc-8.10.5:/usr/lib64:/usr/lib64/ghc-8.10.5/rts

---> Archiving artifacts
ngx_distribution_test.so
x86_64-linux-ghc-8.10.5/
x86_64-linux-ghc-8.10.5/libHSasync-2.2.4-ENjuIeC23kaKyMVDRYThP3-ghc8.10.5.so
x86_64-linux-ghc-8.10.5/libHSsplitmix-0.1.0.4-HVTAcdRNxuE9ndjT7sldq9-ghc8.10.5.so
x86_64-linux-ghc-8.10.5/libHSth-abstraction-0.4.3.0-5HX1AugCZKLKm3ZYKErCAM-ghc8.10.5.so
x86_64-linux-ghc-8.10.5/libHSrts_thr-ghc8.10.5.so

   ...

x86_64-linux-ghc-8.10.5/libHSbifunctors-5.5.11-2fVsEc2ZlypEgv2Pi5nRwa-ghc8.10.5.so
x86_64-linux-ghc-8.10.5/libHSstrict-0.4.0.1-Bs4t4Fhsgeo8grcWS7WJTy-ghc8.10.5.so
x86_64-linux-ghc-8.10.5/libHSdlist-1.0-GVPedlNIGcrCE31hGMMV1G-ghc8.10.5.so

Note that in ghc older than 8.10.6, option -threaded must be replaced with option -lHSrts_thr-ghc$(ghc --numeric-version) because ghc option -flink-rts which is passed by the module internally has first appeared in the said release. Note also that clause ghc-options in the Cabal file is a better place for such a generic option as -threaded.

Now the current working directory contains new files ngx_distribution_test.so and ngx-distribution-test-0.1.0.0.tar.gz and a new directory x86_64-linux-ghc-8.10.5. The tar-file contains the patched shared library and the directory with dependent libraries: it is ready for installation in directory /var/lib/nginx at the target system.

Building with Setup.hs commands

For building custom artifacts, options of hslibdeps must be accessed directly. For this, commands runhaskell Setup.hs configure / build can be used instead of cabal v1-configure / v1-build. Let's change the names of the directory with dependent libraries and the tar-file to deps/ and deps.tar.gz respectively, and also define the rpath directory without using option --prefix.

$ runhaskell Setup.hs configure --user
$ runhaskell Setup.hs build --ghc-options="ngx_distribution_test.hs -o ngx_distribution_test.so -threaded" --hslibdeps-options="-t/var/lib/nginx/deps -ddeps -adeps"

Building dependencies with cabal v2-build

Nowadays, Cabal recommends building packages using Nix-style local builds. This means that dependent packages do not get installed in places known to GHC. However, they can be built inside GHC package environments. Let's build dependencies and put them in a package environment in the current working directory.

$ cabal v2-install --lib --only-dependencies --package-env .
$ cabal v2-install --lib ngx-export-distribution --package-env .
$ sed -i 's/\(^package-id \)/--\1/' .ghc.environment.x86_64-linux-$(ghc --numeric-version)

This sed command comments out all lines that start with word package-id in file .ghc.environment.x86_64-linux-8.10.5 which has been created by the former commands. This prevents the target library from linking against libraries listed in those lines thus making the overall number and the size of dependent libraries as small as possible. If this command breaks the following steps, some of the commented lines can be selectively uncommented.

$ runhaskell --ghc-arg=-package=base --ghc-arg=-package=ngx-export-distribution Setup.hs configure --package-db=clear --package-db=global --package-db="$HOME/.cabal/store/ghc-$(ghc --numeric-version)/package.db" --prefix=/var/lib/nginx

Directory $HOME/.cabal/store/ghc-$(ghc --numeric-version)/package.db contains a GHC package db with all packages built by cabal v2-build, it gets also listed in file .ghc.environment.x86_64-linux-8.10.5.

$ runhaskell --ghc-arg=-package=base --ghc-arg=-package=ngx-export-distribution Setup.hs build --ghc-options="ngx_distribution_test.hs -o ngx_distribution_test.so -threaded"

This should build library ngx_distribution_test.so and link it against Haskell libraries found in the global package db and $HOME/.cabal/store/ghc-$(ghc --numeric-version)/package.db.

With all building approaches shown above, the following list of drawbacks must be taken into account.

  • Utility hslibdeps collects only libraries prefixed with libHS,
  • clean commands such as cabal v1-clean do not delete build artifacts in the current working directory,
  • behavior of Cabal commands other than configure, build and clean is not well defined.

Exported functions

buildSharedLib Source #

Arguments

:: Verbosity

Verbosity level

-> PackageDescription

Package description

-> LocalBuildInfo

Local build info

-> BuildFlags

Build flags

-> IO FilePath 

Builds a shared library.

Runs ghc compiler with the following arguments.

  • -dynamic, -shared, -fPIC, -flink-rts (in ghc 8.10.6 and newer),
  • all arguments listed in ghc-options in the Cabal file,
  • all arguments passed in option --ghc-options from command-line,
  • if arguments do not contain -o path so far, then $pkg.hs, -o $pkg.so.

Returns the path to the built shared library.

patchAndCollectDependentLibs Source #

Arguments

:: Verbosity

Verbosity level

-> FilePath

Path to the library

-> PackageDescription

Package description

-> LocalBuildInfo

Local build info

-> IO () 

Patches the shared library and collects dependent Haskell libraries.

Performs the following steps.

  • Collects all dependent Haskell libraries in a directory with the name equal to the value of $abi which normally expands to $arch-$os-$compiler (or with that overridden in option --hslibdeps-options),
  • adds value $prefix/$abi (or that overridden in option --hslibdeps-options) in the beginning of the list of rpath in the shared library,
  • archives the shared library and the directory with the collected dependent libraries in a tar.gz file.

All steps are performed by utility hslibdeps. It collects all libraries with prefix libHS from the list returned by command ldd applied to the shared library.

ngxExportHooks Source #

Arguments

:: Verbosity

Verbosity level

-> UserHooks 

Build hooks.

Based on simpleUserHooks. Overrides

Other hooks from simpleUserHooks get derived as is. Running them is neither tested nor recommended.

defaultMain :: IO () Source #

A simple implementation of main for a Cabal setup script.

Implemented as

defaultMain = defaultMainWithHooks $ ngxExportHooks normal