hs-pkg-config-0.2.1.0: Create pkg-config configuration files

Copyright(c) 2014 Peter Trsko
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityDeriveDataTypeable, NoImplicitPrelude
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.PkgConfig

Contents

Description

Create pkg-config configuration file from Haskell code using combinators specialized for this purpose. To learn more about pkg-config please read one or both following articles:

Synopsis

Usage

Following code is able to generate foo.pc, a pkg-config configuration file for library named foo:

{-# LANGUAGE OverloadedStrings #-}
module Main (main)
  where

import Data.String (IsString)

import Data.Default.Class (Default(def))
  -- From data-default-class library:
  -- http://hackage.haskell.org/package/data-default-class

import Control.Lens
  -- From lens library:
  -- http://hackage.haskell.org/package/lens

import Data.PkgConfig


libraryBaseName :: IsString a => a
libraryBaseName = "foo"

main :: IO ()
main = writePkgConfig (libraryBaseName ++ ".pc") libPkgConfig
  where
    libPkgConfig = def
        & pkgVariables   .~
            [ ("prefix",     "/usr/local"              )
            , ("includedir", var "prefix" </> "include")
            , ("libdir",     var "prefix" </> "lib"    )
            , ("arch",       "i386"                    )
            ]
        & pkgName        .~ libraryBaseName
        & pkgDescription .~ "Example pkg-config."
        & pkgVersion     .~ version [1, 2, 3]
        & pkgCflags      .~ includes [var "includedir"]
        & pkgRequires    .~ list
            [ "bar" ~> [0], "bar" ~<= [3, 1]
            , "baz" ~= [1, 2, 3]
            ]
        & pkgLibs        .~ options
            [ libraryPath [var "libdir", var "libdir" </> var "arch"]
            , libraries [libraryBaseName]
            ]

Content of generated foo.pc:

prefix=/usr/local
includedir=${prefix}/include
libdir=${prefix}/lib
arch=i386

Name: foo
Description: Example pkg-config.
Version: 1.2.3
Requires: bar > 0, bar <= 3.1, baz = 1.2.3
Cflags: -I"${includedir}"
Libs: -L"${libdir}" -L"${libdir}/${arch}" -lfoo

Note that functions & and .~, used in the example, are from lens library. Please consult its documentation for details.

PkgConfig

Data type that describes whole pkg-config configuration file for one specific library. It also tries to preserve as much of pkg-config philosophy as possible.

Lenses are used for accessing individual fields of PkgConfig data type. Example:

def & pkgVariables .~ [("prefix", "/usr/local")]
    & pkgName      .~ "some library"
    -- ...
    & pkgLibs      .~ includes
        [ var "prefix" </> "include" </> "foo"
        ]

data PkgConfig Source

Representation of pkg-config configuration file.

Lenses

pkgVariables :: Functor f => ([PkgVariable] -> f [PkgVariable]) -> PkgConfig -> f PkgConfig Source

Variable definitions.

pkgName :: Functor f => (Text -> f Text) -> PkgConfig -> f PkgConfig Source

Human-readable name of a library or package. This field is not used by pkg-config tool for queries, because it uses .pc file base name.

pkgDescription :: Functor f => (Text -> f Text) -> PkgConfig -> f PkgConfig Source

Brief description of the package.

pkgUrl :: Functor f => (Text -> f Text) -> PkgConfig -> f PkgConfig Source

URL where people can get more information about and download the package.

pkgVersion :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

Version of the package.

pkgRequires :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

List of packages required by this package and their version bounds.

pkgRequiresPrivate :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

Compiler flags specific to this package and any required libraries that don't support pkg-config. If the required libraries support pkg-config, they should be added to Requires (pkgRequires) or Requires.private (pkgRequiresPrivate).

pkgConflicts :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

An optional field describing packages that this one conflicts with. The version specific rules from the Requires field also apply here. This field also takes multiple instances of the same package. E.g.:

Conflicts: bar < 1.2.3, bar >= 1.3.0.

pkgCflags :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

Compiler flags specific to this package and any required libraries that don't support pkg-config. If the required libraries support pkg-config, they should be added to Requires (pkgRequires) or Requires.private (pkgRequiresPrivate).

pkgLibs :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

Linking flags specific to this package and any required libraries that don't support pkg-config. The same rules as for Cflags (pkgCflags) field apply here.

pkgLibsPrivate :: Functor f => (PkgTemplate -> f PkgTemplate) -> PkgConfig -> f PkgConfig Source

Linking flags for private libraries required by this package but not exposed to applications. The same rules as for Cflags (pkgCflags) field apply here.

Type Aliases

These are used to make type signatures easier to read.

type PkgVariable = (Text, PkgTemplate) Source

Variable definition consisting of its name and value in form of PkgTemplate.

type PkgVersion = PkgTemplate Source

Package version may use variable expansion and so it is represented by PkgConfig.

Serialization

toStrictText :: PkgConfig -> Text Source

Serialize PkgConfig in to strict Text.

toString :: PkgConfig -> String Source

Serialize PkgConfig in to strict Text and then convert it to a String.

I/O

writePkgConfig :: FilePath -> PkgConfig -> IO () Source

Serialize PkgConfig in to strict Text and write it in to a specified file.

PkgTemplate

The pkg-config tool allows variable declaration so that they can later be used in other parts of its configuration file. To give Haskell programmer the same power, this library provides PkgTemplate. One can think of it as a string with named holes, i.e. places where variables will be expanded. Following is example of how two variables, namely prefix and includedir, can be defined inside pkg-config configuration file:

prefix=/usr/local
includedir=${prefix}/include

PkgConfig has a field pkgVariables that is used to define variables and above example can be translated in to:

def & pkgVariables .~
    [ ("prefix", "/usr/local")
    , ("includedir", var "prefix" </> "include")
    ]

Lot of similar properties of String hold for Template as well. Including the fact that Template is monoid and therefore can be concatenated using monoid operations:

>>> strLit "foo" <> strLit "bar"
foobar

Since Template has IsString instance, then, if OverloadedStrings language extension is enabled, it is possible to simplify above example in to:

>>> "foo" <> "bar" :: PkgTemplate
foobar

For consistency instance for Default type class is also provided and it holds following property:

def === mempty

Additionally following properties hold:

lit "" === mempty
var "" =/= mempty

type PkgTemplate = Template Source

Template consists of variables and literal strings. All special characters ('$', '#', '\' and end-of-line sequences) contained in literals are escaped when serialized.

Smart Constructors

var :: Text -> PkgTemplate Source

Construct variable fragment of a template.

>>> var "prefix" <> lit "/bin"
$prefix/bin

lit :: Text -> PkgTemplate Source

Construct literal fragment of a template. This is useful if language extension OverloadedStrings is not enabled.

>>> var "prefix" <> lit "/bin"
$prefix/bin

strLit :: String -> PkgTemplate Source

Create PkgTemplate literal from String by packing it in to strict Text first.

singletonLit :: Char -> PkgTemplate Source

Crate one character long PkgTemplate literal.

Combinators

quote :: PkgTemplate -> PkgTemplate Source

Put quotation marks ('"') around a template.

>>> quote $ var "prefix" </> "include"
"${prefix}/include"
>>> var "prefix" </> quote "dir with spaces"
${prefix}/"dir with spaces"

FilePath-like Combinators

(</>) :: PkgTemplate -> PkgTemplate -> PkgTemplate Source

Put literal "/" between two templates.

>>> var "prefix" </> lit "foo" <.> lit "pc"
${prefix}/foo.pc

(<.>) :: PkgTemplate -> PkgTemplate -> PkgTemplate Source

Put literal "." between two templates.

>>> var "prefix" </> lit "foo" <.> lit "pc"
${prefix}/foo.pc
>>> var "major" <.> var "minor" <.> var "patch"
${major}.${minor}.${patch}

Version Combinators

version :: [Word] -> PkgTemplate Source

Treat list of integers as version number and construct template literal out of it.

>>> version [1, 2, 3]
1.2.3
>>> version [] == mempty
True

versionInt :: [Int] -> PkgTemplate Source

Variant of version that takes list of integers. This function can be used to create PkgTemplate from standard Haskell Version data type.

>>> versionInt . versionBranch $ Version [0, 1, 2] []
0.1.2

(~=) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package of exact version.

>>> "sqlite" ~= [3, 8, 7, 1]
sqlite = 3.8.7.1
>>> list ["sqlite" ~= [3, 8, 7, 1], "alpha" ~= [7, 2]]
sqlite = 3.8.7.1, alpha = 7.2

(~/=) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package not of a specific version.

>>> "alpha" ~/= [7, 2]
alpha != 7.2
>>> list ["sqlite" ~/= [3, 8, 7, 1], "alpha" ~/= [7, 2]]
sqlite != 3.8.7.1, alpha != 7.2

(~<) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package with version greater or less then specified value.

>>> "alpha" ~< [7, 3]
alpha < 7.3
>>> list ["sqlite" ~< [3, 9], "alpha" ~< [7, 3]]
sqlite < 3.9, alpha < 7.3

(~>) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package with version greater then specified value.

>>> "sqlite" ~> [3, 8]
sqlite3 > 3.8
>>> list ["sqlite" ~> [3, 8], "alpha" ~> [7, 1]]
sqlite > 3.8, alpha > 7.1

(~<=) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package with version greater or less or equal then specified value.

(~>=) :: Text -> [Word] -> PkgTemplate Source

Dependency on a package with version greater or equal then specified value.

Options Combinators

option :: Text -> PkgTemplate -> PkgTemplate Source

Create template starting with option followed by its argument. Argument is quoted using quote function to prevent problems with spaces in directory names.

>>> option "--foo=" $ var "prefix" </> "some dir"
--foo="${prefix}/some dir"

Following property holds:

forall t. option "" t === quote t

strOption :: String -> PkgTemplate -> PkgTemplate Source

Same as option, but takes String instead of strict Text.

includes :: [PkgTemplate] -> PkgTemplate Source

Take list of templates and make compiler include options. Template for include directory is wrapped in quotes (see quote and option functions).

>>> let d = var "prefix" </> "include" in includes [d, d </> var "arch"]
-I"${prefix}/include" -I"${prefix}/include/${arch}"
>>> includes [var "prefix" </> "some dir"]
-I"${prefix}/some dir"

libraries :: [PkgTemplate] -> PkgTemplate Source

Take list of templates and make compiler library options.

>>> libraries ["m", "rt", "foo"]
-lm -lrt -lfoo

libraryPath :: [PkgTemplate] -> PkgTemplate Source

Take list of templates and make compiler library path options. Template for include directory is wrapped in quotes (see quote and option functions).

>>> let l = var "prefix" </> lit "lib" in libraryPath [l, l </> var "arch"]
-L"${prefix}/lib" -L"${prefix}/lib/${arch}"

Specialized Folds

list :: [PkgTemplate] -> PkgTemplate Source

Concatenate templates by inserting coma (',') in between.

>>> list ["foo" .= [1,2,3], "bar" .> [0], "bar" .< [3,1]]
foo = 1.2.3, bar > 0, bar < 3.1

Following properties hold:

list [] === mempty
forall t. list [t] === t

options :: [PkgTemplate] -> PkgTemplate Source

Concatenate templates by inserting space (' ') in between.

>>> options ["-I" <> var "prefix" </> "lib", "-I" <> var "extra"]
-I${prefix}/lib -I${extra}

Following properties hold:

options [] === mempty
forall t. options [t] === t

separatedBy :: Text -> [PkgTemplate] -> PkgTemplate Source

Put specified text between templates.

Following properties hold:

forall s. separatedBy s [] === mempty
forall s t. separatedBy s [t] === t

Example:

>>> separatedBy ", " ["foo", "bar", "baz"]
foo, bar, baz

Queries

variables :: PkgTemplate -> [Text] Source

List all variables mentioned in PkgTemplate.

>>> variables $ var "foo" </> "bar" </> var "baz"
["foo","baz"]