core-program-0.6.8.0: Opinionated Haskell Interoperability
Safe HaskellSafe-Inferred
LanguageHaskell2010

Core.Program.Metadata

Description

Digging metadata out of the description of your project, and other useful helpers.

Synopsis

Documentation

data Version Source #

Information about the version number of this piece of software and other related metadata related to the project it was built from. This is supplied to your program when you call configure. This value is used if the user requests it by specifying the --version option on the command-line.

Simply providing an overloaded string literal such as version "1.0" will give you a Version with that value:

{-# LANGUAGE OverloadedStrings #-}

main :: IO ()
main = do
    context <- configure "1.0" None (simpleConfig ...

For more complex usage you can populate a Version object using the fromPackage splice below. You can then call various accessors like versionNumberFrom to access individual fields.

Since: 0.6.7

Instances

Instances details
IsString Version Source # 
Instance details

Defined in Core.Program.Metadata

Methods

fromString :: String -> Version #

Show Version Source # 
Instance details

Defined in Core.Program.Metadata

Lift Version Source # 
Instance details

Defined in Core.Program.Metadata

Methods

lift :: Quote m => Version -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Version -> Code m Version #

Splice

fromPackage :: Q Exp Source #

This is a splice which includes key built-time metadata, including the number from the version field from your project's .cabal file (as written by hand or generated from package.yaml). This uses the evil TemplateHaskell extension.

While we generally discourage the use of Template Haskell by beginners (there are more important things to learn first) it is a way to execute code at compile time and that is what what we need in order to have the version number extracted from the .cabal file rather than requiring the user to specify (and synchronize) it in multiple places.

To use this, enable the Template Haskell language extension in your Main.hs file. Then use the special $( ... ) "insert splice here" syntax that extension provides to get a Version object with the desired metadata about your project:

{-# LANGUAGE TemplateHaskell #-}

version :: Version
version = $(fromPackage)

main :: IO ()
main = do
    context <- configure version None (simpleConfig ...
    executeWith context program

program :: Program None ()
program = do
    ...

In addition to metadata from the Haskell package, we also extract information from the Git repository the code was built within, if applicable. When the program is built within a source code checkout (as is typical in continuous integration & continuous deployment systems) then the repository is queried for the SHA1 hash, branch name, and for whether the checkout is clean.

The resultant --version output might look like the following:

$ ping --version
ip-utils v2.0.1.9, f18ec7b

If, on the other hand, you had been developing locally you'll see this:

$ ping --version
ip-utils v2.0.1.9, f18ec7b (dirty)

signifying that there are uncommitted files in your local tree.

If you are building the program from a relese tarball, this mechanism will omit reporting any information about the state of a Git repository as it is not to hand.

Since: 0.6.7

Source code

__LOCATION__ :: HasCallStack => SrcLoc Source #

Access the source location of the call site.

This is insanely cool, and does not require you to turn on the CPP or TemplateHaskell language extensions! Nevertheless we named it with underscores to compliment the symbols that CPP gives you; the double underscore convention holds across many languages and stands out as a very meta thing, even if it is a proper Haskell value.

We have a Render instance that simply prints the filename and line number. Doing:

main :: IO ()
main = execute $ do
    writeR __LOCATION__

will give you:

tests/Snipppet.hs:32

This isn't the full stack trace, just information about the current line. If you want more comprehensive stack trace you need to add HasCallStack constraints everywhere, and then...

Since: 0.4.3

Orphan instances

Render SrcLoc Source # 
Instance details

Associated Types

type Token SrcLoc #