cartel-0.18.0.2: Specify Cabal files in Haskell

Safe HaskellSafe
LanguageHaskell2010

Cartel

Contents

Description

Cartel - a library to specify Cabal files in Haskell

The Cabal file format works very well for small projects. However, in big projects with a library, many executables, and test suites, some irritations emerge. You need to specify dependencies in multiple places, leading to redundancy. You also have to manually add in new modules, make sure you list all modules (a real pain with executables, as problems may arise only after you build a distribution tarball), and update your module lists when you refactor.

Specifying your Cabal files in Haskell rather than in a plain-text file format helps deal with a lot of these problems. You have the full power of Haskell to make definitions in one place and then reuse them. You can also dynamically read a tree of modules and use the result, thus avoiding the need to manually update your module lists.

A disadvantage to Cartel is that is more verbose than a vanilla Cabal file. In addition, you also have to remember to generate the new Cabal file whenever you change the script that generates your Cabal file.

To some extent, Cartel uses the Haskell type system to prevent you from making mistakes in your Cabal file. For example, the Betsy type prevents you from using flags that you have not declared, and you can't put an exposedModules field in anything but a library. However, Cartel does not prevent against all errors. For example, Cartel does nothing to prevent you from applying a function that calls for a NonEmptyString to a string that is, in fact, empty. Another example is that Cabal requires executables to have a main-is field, but Cartel does not force you to include one. Ultimately your Cabal file might still have errors that you have to fix by changing the program that generates the file.

I highly recommend that you use Cartel with stack, a Haskell build tool. Stack is available at

https://www.haskellstack.org

Using stack means you can easily specify the exact package set with which to build your Cabal file, which helps ensure that it builds well into the future regardless of what compiler version someone happens to have installed. I recommend setting up a different Cabal package whose sole job is to build your Cabal file. If you are on a UNIX-like system, use the cartel-init program, which is included in the Cartel package. cartel-init establishes a skeleton file tree for a new package. Run cartel-init first to create an empty tree, and then create your package modules (or copy them into the tree, if you are converting an existing package to Cartel.)

For example, to create a new package named hello, I would run the following:

$ cartel-init github --author 'Omari Norman' \
   --maintainer 'omari@smileystation.com' \
   --bsd3 --username massysett hello

The --author and --maintainer options specify the author and maintainer fields for the Cabal file. The --bsd3 option makes your new package have the BSD3 license; otherwise, you will get an "All Rights Reserved" license. The --username option gives your Github username, and hello is the name of the package itself.

This command creates a directory tree that looks like this:

hello/
Main project directory. Contains two packages: one to build the Cabal file, and one main package
hello/LICENSE
BSD3 license file
hello/README.md
This is NOT distributed with the main Cabal package. It describes how to build this project.
hello/buildprep
With "hello" as the current directory, run "sh buildprep" to generate the Cabal file.
hello/gen-hello-cabal/
Directory containing a package that builds the Cabal file.
hello/gen-hello-cabal/Setup.hs
For the package that builds the Cabal file.
hello/gen-hello-cabal/buildprep
Run from this directory to generate the Cabal file.
hello/gen-hello-cabal/gen-hello-cabal.cabal
Cabal file for the pacakge that generates the Cabal file.
hello/gen-hello-cabal/gen-hello-cabal.hs
Module with program that generates the Cabal file. Edit this to change the generated Cabal file.
hello/gen-hello-cabal/stack.yaml
Specifies stack resolver for package that builds the Cabal file.
hello/hello/
Directory with the Cabal package that you would distribute on Hackage.
hello/hello/LICENSE
BSD3 license.
hello/hello/README.md
This is distributed with the project's Cabal package.
hello/hello/Setup.hs
For the main Cabal package.
hello/hello/buildprep
From this directory, run "sh buildprep" to generate the Cabal file.
hello/hello/lib/
Empty directory. Place your library modules in here.
hello/hello/stack.yaml
Has the resolver to use for the main package.

After running cartel-init, you will need to edit the gen-yourpackage-cabal.hs file to add (at a minimum) a synopsis, description, and any additional build-depends.

For more information on cartel-init, run:

$ cartel-init --help
$ cartel-init cabal --help
$ cartel-init tree --help
$ cartel-init git --help
$ cartel-init github --help

Everything you usually need is in this module. Other Cartel modules contain implementation details. See first the NonEmptyString type synonym, which has important details on how to regard Strings and NonEmptyStrings as you read the documentation.

Hopefully this module's documentation is organized so that top-to-bottom reading will make sense.

Synopsis

Basic types and classes

data Word :: * #

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word 
Enum Word 

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word 

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Num Word 

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word 
Real Word 

Methods

toRational :: Word -> Rational #

Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word 

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int

Renderable Version Source # 
Functor (URec Word) 

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word) 

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Traversable (URec Word) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Generic1 (URec Word) 

Associated Types

type Rep1 (URec Word :: * -> *) :: * -> * #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) 

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p) 

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

data URec Word

Used for marking occurrences of Word#

data URec Word = UWord {}
type Rep1 (URec Word) 
type Rep1 (URec Word) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))
type Rep (URec Word p) 
type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))

type NonEmptyString = String Source #

A non-empty string. This string should never be empty. It is used where, for example, a field in a Cabal file is required to have a value and that value cannot be empty. In contrast, Cartel uses an ordinary String for values that can be empty.

This is only a type synonym, so nothing in the type system enforces that these strings must be non-empty. Typically though, Cabal will give you grief about the file that Cartel generates if you used an empty value for a NonEmptyString.

type Version = [Word] Source #

A version number. The Cabal documentation says this "usually" consists of a sequence of natural numbers separated by dots. Though this suggests that a version number could contain something other than natural numbers, in fact the types in the Cabal library do not allow anything other than numbers and you will get a parse error if you try to use anything else.

Therefore Cartel's Version type only allows a list of Word, as each number cannot be negative. In addition, this list should never be empty. However, this is just a type synonym for a list of Word, so the type system does not enforce the requirement that this list be non-empty.

Sections

data Section Source #

A single section in a Cabal file; this may be a source repository, executable, test suite, or benchmark. You build a Section with the repository, executable, testSuite, and benchmark functions.

Repositories

Version control systems

data Vcs Source #

Version control systems.

Instances

Eq Vcs Source # 

Methods

(==) :: Vcs -> Vcs -> Bool #

(/=) :: Vcs -> Vcs -> Bool #

Ord Vcs Source # 

Methods

compare :: Vcs -> Vcs -> Ordering #

(<) :: Vcs -> Vcs -> Bool #

(<=) :: Vcs -> Vcs -> Bool #

(>) :: Vcs -> Vcs -> Bool #

(>=) :: Vcs -> Vcs -> Bool #

max :: Vcs -> Vcs -> Vcs #

min :: Vcs -> Vcs -> Vcs #

Show Vcs Source # 

Methods

showsPrec :: Int -> Vcs -> ShowS #

show :: Vcs -> String #

showList :: [Vcs] -> ShowS #

Renderable Vcs Source # 

Methods

render :: Vcs -> String Source #

cvs Source #

Arguments

:: NonEmptyString

The named module

-> Vcs 

Repository kinds

Building repositories

data Repository Source #

A single repository section. This is an instance of Monoid, so to get a blank Repository section, use mempty.

Constructors

Repository 

Fields

githubHead Source #

Arguments

:: NonEmptyString

The Github account name

-> NonEmptyString

The Github project name within the account

-> Section 

Creates a Section that is a Repository for a Github head. For example, for Cartel, use githubHead "massysett" "cartel".

repository :: Repository -> Section Source #

Creates a Section for a repository.

Logicals

invert :: Condition -> Condition Source #

Like not, which is what I would have named it but for the conflict. Only Conditions have this sort of operation; Cabal does not have a (documented, at least) way to express this for package constraints.

Constraints

lt :: Version -> Constraint Source #

Less than

gt :: Version -> Constraint Source #

Greater than

eq :: Version -> Constraint Source #

Equal to

ltEq :: Version -> Constraint Source #

Less than or equal to

gtEq :: Version -> Constraint Source #

Greater than or equal to

anyVersion :: Constraint Source #

Matches any version at all (in a Cabal file, this is represented as an empty string).

Conditionals

system :: NonEmptyString -> Condition Source #

Operating system; tested against System.Info.os on the target system.

arch :: NonEmptyString -> Condition Source #

Argument is matched against System.Info.arch on the target system.

impl :: Compiler -> Constraint -> Condition Source #

Tests for the configured Haskell implementation.

flag :: FlagName -> Condition Source #

Evaluates to the current assignment of the flag of the given name. Flag names are case insensitive. Testing for flags that have not been introduced with a flag section is an error.

true :: Condition Source #

Always true.

false :: Condition Source #

Always false.

condBlock Source #

Arguments

:: HasBuildInfo a 
=> Condition

Condition to satisfy

-> (a, [a])

Use these results if condition is true

-> [a]

Use these results if condition if false

-> a 

Builds if statements. For example:

condition (flag "buildExe") (buildable True, []) [buildable False]

A little more complicated:

condition (flag "buildExe" &&& system "windows")
  (buildable True, []) [buildable False]

Packages

data Package Source #

A single package, consisting of a package name and an optional set of constraints. Used when specifying buildDepends, buildTools, and pkgConfigDepends.

Some functions exist to ease the creation of a Package. For a package with no version constrains, simply do something like unconstrained "QuickCheck". Common use cases are covered in the functions in the "Package Helpers" section below. For something more complicated, use the functions in the "Logicals" sections above, along with the &&& and ||| combinators, to create your own Constraint and then use it with the package function.

package Source #

Arguments

:: NonEmptyString

The name of the package

-> Constraint

Version constraints.

-> Package 

Builds a Package.

Package helpers

closedOpen Source #

Arguments

:: NonEmptyString

Package name

-> Version

Version number for lower bound

-> Version

Version number for upper bound

-> Package

Resulting Package

Creates a package interval that is closed on the left, open on the right. Useful for the common case under the PVP to specify that you depend on a version that is at least a particular version, but less than another version.

closedOpen "bytestring" [0,17] [0,19] ==> bytestring >= 0.17 && < 0.19

apiVersion :: NonEmptyString -> Version -> Package Source #

Specifies a particular API version. Useful to lock your package dependencies down to a particular API version.

apiVersion "base" [1] ==> base >= 1 && < 2
apiVersion "base" [1,2] ==> base >= 1.2 && < 1.3
apiVersion "base" [1,2,3] ==> base >= 1.2.3 && < 1.2.4

nextBreaking :: NonEmptyString -> Version -> Package Source #

Depends on the version given, up to the next breaking API change.

nextBreaking "base" [4] ==> base >= 4 && < 4.1
nextBreaking "base" [4,1] ==> base >= 4.1 && < 4.2
nextBreaking "base" [4,7,0,0] ==> base >= 4.7.0.0 && < 4.8

nextMajor :: NonEmptyString -> Version -> Package Source #

Depends on the version given, up to the next time the first digit increments. Useful for base.

nextBreaking "base" [4] ==> base >= 4 && < 5

exactly :: NonEmptyString -> Version -> Package Source #

Depends on exactly this version only.

exactly "base" [4,5,0,0] ==> base ==4.5.0.0

atLeast :: NonEmptyString -> Version -> Package Source #

Depends on this version, or any greater version.

atLeast "base" [4,5,0,0] ==> version >= 4.5.0.0

unconstrained Source #

Arguments

:: NonEmptyString

Name of package

-> Package 

Allows any version of a package.

Build information

Libraries, executables, test suites, and benchmarks all share common fields for build information. BuildInfoField represents these common fields, and HasBuildInfo is a typeclass encompassing libraries, executables, test suites, and benchmarks. You can build these fields for any of these sections using the functions and values listed here.

data BuildInfoField Source #

A single field of build information. This can appear in a Library, Executable, TestSuite, or Benchmark.

Instances

Eq BuildInfoField Source # 
Ord BuildInfoField Source # 
Show BuildInfoField Source # 
RenderableIndented BuildInfoField Source #

Contains many lists of items. Items that might contain spaces or other troublesome characters are rendered quoted. In particular, this includes filenames. Items that are highly unlikely to contain troublesome characters (such as compiler options) are not quoted.

haskell98 :: HasBuildInfo a => a Source #

Sets Haskell 98 as the default-language.

Currently not documented in Cabal, see

https://github.com/haskell/cabal/issues/1894

haskell2010 :: HasBuildInfo a => a Source #

Sets Haskell 2010 as the default-language.

Currently not documented in Cabal, see

https://github.com/haskell/cabal/issues/1894

buildDepends :: HasBuildInfo a => [Package] -> a Source #

A list of packages needed to build this component

otherModules :: HasBuildInfo a => [NonEmptyString] -> a Source #

Modules used but not exposed. For libraries, these are hidden modules; for executable, these are auxiliary modules to be linked with the file in the main-is field.

modules can help greatly with maintenance of this field.

hsSourceDirs :: HasBuildInfo a => [NonEmptyString] -> a Source #

Root directories for the module hierarchy

extensions :: HasBuildInfo a => [NonEmptyString] -> a Source #

Haskell extensions used by every module. With version 1.22 of the Cabal library, using this field might get you this warning:

Warning: For packages using 'cabal-version: >= 1.10' the
'extensions' field is deprecated. The new 'default-extensions'
field lists extensions that are used in all modules in the
component, while the 'other-extensions' field lists extensions
that are used in some modules, e.g. via the {-# LANGUAGE #-}
pragma.

defaultExtensions :: HasBuildInfo a => [NonEmptyString] -> a Source #

Default extensions. See extensions for details. Currently undocumented, see https://github.com/haskell/cabal/issues/1517

otherExtensions :: HasBuildInfo a => [NonEmptyString] -> a Source #

Other extensions. See extensions for details. Currently undocumented, see https://github.com/haskell/cabal/issues/1517

buildTools :: HasBuildInfo a => [Package] -> a Source #

Programs needed to build this package, such as c2hs.

buildable :: HasBuildInfo a => Bool -> a Source #

Is this component buildable?

includes :: HasBuildInfo a => [NonEmptyString] -> a Source #

Header files to be included in any compilations via C. Applies to both header files that are already installed on the system and to those coming with the package to be installed.

installIncludes :: HasBuildInfo a => [NonEmptyString] -> a Source #

Header files to be installed into $libdir/includes when the package is installed. These files should be found in relative to the top of the source tree or relative to one of the directories listed in include-dirs.

includeDirs :: HasBuildInfo a => [NonEmptyString] -> a Source #

List of diretories to search for header files when dealing with C compilations.

cSources :: HasBuildInfo a => [NonEmptyString] -> a Source #

C sources to be compiled and lined with the Haskell files.

extraLibraries :: HasBuildInfo a => [NonEmptyString] -> a Source #

Extra libraries to link with.

extraLibDirs :: HasBuildInfo a => [NonEmptyString] -> a Source #

Directories to search for libraries.

ccOptions :: HasBuildInfo a => [NonEmptyString] -> a Source #

C Compiler options.

cppOptions :: HasBuildInfo a => [NonEmptyString] -> a Source #

C Preprocessor options. Undocumented, see https://github.com/haskell/cabal/issues/646

ldOptions :: HasBuildInfo a => [NonEmptyString] -> a Source #

Linker options.

pkgConfigDepends :: HasBuildInfo a => [Package] -> a Source #

List of pkg-config packages needed to build this component.

frameworks :: HasBuildInfo a => [NonEmptyString] -> a Source #

OS X frameworks.

BuildsExe

Benchmarks, test suites, and executables have common fields; the BuildsExe class captures these.

class BuildsExe a where Source #

Sections that build executables. These are the Executable, Benchmark, and TestSuite sections.

Minimal complete definition

mainIs

Methods

mainIs :: NonEmptyString -> a Source #

Overloaded function allowing you to use mainIs for an Executable, Benchmark, or TestSuite section.

Exitcode executables

Test suites and benchmarks are capable of building things of type exitcode-stdio-1.0; the BuildsExitcode class reflects this.

class BuildsExitcode a where Source #

Sections that build executables that can be exitcode-stdio-1.0. These are the Benchmark and TestSuite sections.

Minimal complete definition

exitcodeStdio

Methods

exitcodeStdio :: a Source #

Returns a field that is exitcode-stdio-1.0

exitcodeFields Source #

Arguments

:: (BuildsExitcode a, BuildsExe a) 
=> NonEmptyString

Value for main-is field

-> [a] 

Builds two fields. The first indicates that this is an exitcode-stdio-1.0 executable; the second is the appropriate main-is field.

Betsy

data Betsy m a Source #

Computations that can create and use Cabal flags. Use of this type, along with the defaultMain function ensures that any FlagName you use has been properly set up by using makeFlag. That way, you don't use flags in a flag without actually declaring the flag. When defaultMain creates your Cabal file, it will print the necessary Flag sections.

Betsy is parameterized on a type, m. When this type is a monad, Betsy is also a monad, allowing you to use use the usual monad combinators and do notation. Betsy is also a monad transformer.

Instances

MonadTrans Betsy Source # 

Methods

lift :: Monad m => m a -> Betsy m a #

Monad m => Monad (Betsy m) Source # 

Methods

(>>=) :: Betsy m a -> (a -> Betsy m b) -> Betsy m b #

(>>) :: Betsy m a -> Betsy m b -> Betsy m b #

return :: a -> Betsy m a #

fail :: String -> Betsy m a #

Functor m => Functor (Betsy m) Source # 

Methods

fmap :: (a -> b) -> Betsy m a -> Betsy m b #

(<$) :: a -> Betsy m b -> Betsy m a #

(Monad m, Functor m) => Applicative (Betsy m) Source # 

Methods

pure :: a -> Betsy m a #

(<*>) :: Betsy m (a -> b) -> Betsy m a -> Betsy m b #

(*>) :: Betsy m a -> Betsy m b -> Betsy m b #

(<*) :: Betsy m a -> Betsy m b -> Betsy m a #

MonadIO m => MonadIO (Betsy m) Source # 

Methods

liftIO :: IO a -> Betsy m a #

Flags

data FlagName Source #

The name of a flag. Only makeFlag creates flags; it will return a FlagName to you. You can then use that FlagName in a conditional using flag.

data FlagOpts Source #

Options for flags, except for the flag's name.

Constructors

FlagOpts 

Fields

  • flagDescription :: String

    A one-line description of what the flag does; this is optional.

  • flagDefault :: Bool

    Is this flag on or off by default?

  • flagManual :: Bool

    If a flag is manual, Cabal will not change its value. If a flag is not manual, Cabal will change its value automatically to attempt to satisfy the package's dependencies.

data Flag Source #

The name of a flag, paired with its options.

Constructors

Flag FlagName FlagOpts 

Instances

makeFlag Source #

Arguments

:: Applicative m 
=> NonEmptyString

Name of flag

-> FlagOpts

Options for the flag

-> Betsy m FlagName

This operation will fail if there is already a flag with the name you gave.

Creates new flags.

currentFlags :: Applicative f => Betsy f [Flag] Source #

Returns a list of all flags made so far.

Libraries

A library consists of one or more LibraryFields. Typically you will return these fields inside of the Betsy type through the defaultMain function. To build a LibraryField, you will mostly use the bindings in the "Build Information" section of this module. You will also need exposedModules and you might use exposed and condBlock.

exposed :: Bool -> LibraryField Source #

Whether a library is exposed. GHC can hide libraries.

exposedModules :: [NonEmptyString] -> LibraryField Source #

A library's exposed modules. modules can help you generate this, without you having to manually list each module and keep the list up to date.

Executables

An executable consists of one more more ExecutableFields. You build an executable by passing one or more ExecutableFields to the executable function. To get an ExecutableField, you will mostly use the bindings in the "Build Information" section of this module, as well as mainIs. You might also need condBlock.

executable Source #

Arguments

:: NonEmptyString

The name of the executable that Cabal will build.

-> [ExecutableField]

An executable can contain zero or more ExecutableFields.

-> Section 

Builds a Section for executable files.

Test suites

A test suite consists of one more more TestSuiteFields. You build an test suite by passing one or more TestSuiteFields to the testSuite function. To get a TestSuiteField, you will mostly use the bindings in the "Build Information" section of this module. You might also need the testModule, exitcodeStdio, mainIs, detailed, condBlock, and exitcodeFields bindings.

testModule :: NonEmptyString -> TestSuiteField Source #

The module exporting the tests symbol. This is required when using Detailed and disallowed when using ExitcodeStdio.

testSuite Source #

Arguments

:: NonEmptyString

The executable name for the resulting test suite

-> [TestSuiteField]

Zero or more TestSuiteFields.

-> Section 

Builds a Section for test suites.

Benchmarks

A benchmark consists of one more more BenchmarkFields. You build an benchmark by passing one or more BenchmarkFields to the benchmark function. To get an BenchmarkField, you will mostly use the bindings in the "Build Information" section of this module. You might also need the exitcodeStdio, exitcodeFields, and condBlock bindings.

benchmark Source #

Arguments

:: NonEmptyString

The name of the executable file that will be the benchmark

-> [BenchmarkField]

Zero or more benchmark fields.

-> Section 

Builds a Section for benchmarks.

Getting module lists

fileExtensions :: [String] Source #

Common extensions of Haskell files and files that are preprocessed into Haskell files. Includes:

  • hs (Haskell)
  • lhs (literate Haskell)
  • gc (greencard)
  • chs (c2hs)
  • hsc (hsc2hs)
  • y and ly (happy)
  • x (alex)
  • cpphs

modulesWithExtensions Source #

Arguments

:: MonadIO m 
=> [NonEmptyString]

Look for files that have these extensions. fileExtensions covers the most common cases. Files without one of these extensions are ignored. Files and directories that do not begin with an uppercase letter are ignored. (This also ignores files that start with a dot.) Directories with a dot anywhere in the name are ignored.

Do not include the leading dot with the extension. For example, to look for Haskell and literate Haskell files only, use

["hs", "lhs"]
-> FilePath

Start searching within this directory.

-> Betsy m [NonEmptyString]

A list of Haskell modules in the given directory tree. The file contents are not examined; only the file names matter. Returned as a list of dotted names.

Gets all Haskell modules in a given directory tree. Allows you to specify what extensions you are interested in. For this to work best, you will want to keep all your library modules in their own directory, such as lib/. You can also separate executables and test suites this way. hsSourceDirs will then tell Cabal to use these directories.

Properties

Build types

Licenses

data Properties Source #

Global package properties. Is an instance of Monoid so to get a blank Properties use mempty, for example:

properties = mempty
 { name = "mypackage"
 , version = [0,1]
 , cabalVersion = Just (1,10)
 , buildType = Just simple
 -- etc.  Fields you don't supply will be blank.
 }

Many of these fields hold a Maybe type. Values that are Nothing will generate no output in the resulting Cabal file. Other fields are a String type. Empty strings will generate no output in the resulting Cabal file. Other values are lists; empty lists generate no output in the resulting Cabal file.

Constructors

Properties 

Fields

  • name :: String

    The unique name for the package, without the version number.

  • version :: Version

    The package version number, which is always a list of natural numbers.

  • cabalVersion :: Maybe (Word, Word)

    The version of the Cabal specification to use. As of 2016-01-30 I can find no documentation on what these different versions are. cabal init of the cabal-install program version 1.22.6.0 is using 1.10 as the default value here.

  • buildType :: Maybe BuildType
     
  • license :: Maybe License

    The type of license under which the package is distributed

  • licenseFile :: String

    The name of a file or files containing the precise copyright license. The license file will be installed with the package. If you have mulitple license files, use the licenseFiles field instead of, or in addition to, this field.

  • licenseFiles :: [NonEmptyString]
     
  • copyright :: String

    A freeform copyright string, for instance, Copyright: (c) 2006-2007 Joe Bloggs

  • author :: String

    The original author of the package.

  • maintainer :: String

    According to the "Developing Cabal Packages" document, this should simply be an email address.

  • stability :: String

    The stability level of the package, e.g. alpha", experimental, provisional, stable@, etc.

  • homepage :: String

    URL for package homepage.

  • bugReports :: String

    URL where user should send bug reports. This can be a mailto: for mailed bug reports or an http or https URL for an online bug tracking system.

  • packageUrl :: String

    Location of a source bundle for the package. The distribution should be a Cabal package.

  • synopsis :: String

    Very short description of the package, for use in a table of packages.

  • description :: [String]

    Description of the package. This can be several paragraphs.

  • category :: String

    Classification category for Hackage. There is not much of an organizational system to these categories.

  • testedWith :: [(Compiler, Constraint)]

    LIst of compilers and versions against which the package has been tested (or built).

  • dataFiles :: [NonEmptyString]

    List of files to be installed for run-time use by the package. This is useful for packages that have a large amount of static data.

  • dataDir :: String

    The directory where Cabal looks for data files to install, relative to the source directory. By default, Cabal will look in the source directory itself.

  • extraSourceFiles :: [NonEmptyString]

    A list of additional files to be included in source distributions built with setup sdist. As with dataFiles it can include a limited form of * wildcards in file names.

  • extraDocFiles :: [NonEmptyString]

    A list of additional files to be included in source distributions, and also copied to the html directory when Haddock documentation is generated. As with data-files it can use a limited form of * wildcards in file names.

  • extraTmpFiles :: [NonEmptyString]

    A list of additional files or directories to be removed by setup clean. These would typically be additional files created by additional hooks.

Generating Cabal files

defaultMain Source #

Arguments

:: Betsy IO (Properties, [LibraryField], [Section])

Computation that creates the package information. Betsy creates Flags. The Betsy type constructor is appled to IO so that functions such as modules can do IO to query the file system.

-> IO ()

Prints Cabal file to standard output if there were no errors along the way; otherwise, prints a message to standard error and exits unsuccessfully.

Generates a Cabal file. If you have no library, just leave the list of LibraryField empty. Include any and all executables, test suites, benchmarks, and repositories in the list of Section. Ensures that the generated Cabal file also includes any flags you made with makeFlag. If there is an error (such as a duplicate flag) an error message is printed to standard error and the program invokes exitFailure; otherwise, the generated Cabal file is printed to standard output and the program invokes exitSuccess. Output will always be UTF-8, consistent with Cabal's requirements.

Includes a header showing that the Cabal file was auto-generated and the program name that generated the Cabal file, along with when it was generated. This gives a clue to readers who see a Cabal file in the distributed tarball but who would get confused when there isn't one in the version controlled sources. To omit the header, use defaultMainWithHeader.

defaultMainWithHeader Source #

Arguments

:: (Cabal -> IO String)

Function that generates a header. This header will be prepended to the resulting Cabal file; for instance, you might place comments in this header. This function is applied to the resulting Cabal record. For no header, just use const (return "") here.

The Cabal type is not exported from this module to keep the number of exported bindings down; you can import it from Cartel.Ast.

-> Betsy IO (Properties, [LibraryField], [Section])

Computation that creates the package information. Betsy creates Flags. The Betsy type constructor is appled to IO so that functions such as modules can do IO to query the file system.

-> IO ()

Prints Cabal file to standard output if there were no errors along the way; otherwise, prints a message to standard error and exits unsuccessfully.

Like defaultMain but allows you to specify what header to prepend to the output (if any).