| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Cartel.Ast
Contents
Description
The Cartel abstract syntax tree
Use this module if you want access to the data constructors in the AST; the functions and values exported through Cartel should be enough for most uses. Use of this module will not violate any invariants; this stuff is in a separate module merely for the sake of tidiness of the documentation in Cartel.
Cabal already has an AST that it uses. Cartel could, perhaps, have re-used these structures. Cartel does not do this for three reasons. First, the Cabal API is a bit untidy, partially because it has to do things that Cartel doesn't have to worry about, but also because the comments in the Cabal modules themselves indicate that the whole thing could use a refactoring. Second, the Cabal developers make no commitment to keep that API stable. Third, the Cartel API tries only to replicate format of the plain-text Cabal file, which will be much more stable than the Cabal API.
- class Blank a where
- blank :: a
- data RepoKind
- repoHead :: RepoKind
- repoThis :: RepoKind
- data Vcs
- darcs :: Vcs
- monotone :: Vcs
- archVcs :: Vcs
- bazaar :: Vcs
- mercurial :: Vcs
- svn :: Vcs
- git :: Vcs
- cvs :: NonEmptyString -> Vcs
- data Repository = Repository {}
- githubHead :: NonEmptyString -> NonEmptyString -> Section
- repository :: Repository -> Section
- data CondLeaf
- data Logical
- newtype OrEqualTo = OrEqualTo Bool
- data VersionComp
- data ConstrTree
- data Constraint
- data Condition
- invert :: Condition -> Condition
- data CondBlock a = CondBlock {}
- class LogicTree a where
- lt :: Version -> Constraint
- gt :: Version -> Constraint
- eq :: Version -> Constraint
- ltEq :: Version -> Constraint
- gtEq :: Version -> Constraint
- anyVersion :: Constraint
- closedOpen :: NonEmptyString -> Version -> Version -> Package
- apiVersion :: NonEmptyString -> Version -> Package
- nextBreaking :: NonEmptyString -> Version -> Package
- nextMajor :: NonEmptyString -> Version -> Package
- exactly :: NonEmptyString -> Version -> Package
- unconstrained :: NonEmptyString -> Package
- condBlock :: HasBuildInfo a => Condition -> (a, [a]) -> [a] -> a
- system :: NonEmptyString -> Condition
- arch :: NonEmptyString -> Condition
- impl :: Compiler -> Constraint -> Condition
- flag :: FlagName -> Condition
- true :: Condition
- false :: Condition
- type Version = [Word]
- data Package = Package NonEmptyString Constraint
- package :: NonEmptyString -> Constraint -> Package
- data DefaultLanguage
- haskell98 :: HasBuildInfo a => a
- haskell2010 :: HasBuildInfo a => a
- data BuildInfoField
- = BuildDepends [Package]
- | OtherModules [NonEmptyString]
- | HsSourceDirs [NonEmptyString]
- | Extensions [NonEmptyString]
- | DefaultExtensions [NonEmptyString]
- | OtherExtensions [NonEmptyString]
- | BuildTools [Package]
- | Buildable Bool
- | GHCOptions [NonEmptyString]
- | GHCProfOptions [NonEmptyString]
- | GHCSharedOptions [NonEmptyString]
- | HugsOptions [NonEmptyString]
- | Nhc98Options [NonEmptyString]
- | Includes [NonEmptyString]
- | InstallIncludes [NonEmptyString]
- | IncludeDirs [NonEmptyString]
- | CSources [NonEmptyString]
- | ExtraLibraries [NonEmptyString]
- | ExtraLibDirs [NonEmptyString]
- | CCOptions [NonEmptyString]
- | CPPOptions [NonEmptyString]
- | LDOptions [NonEmptyString]
- | PkgConfigDepends [Package]
- | Frameworks [NonEmptyString]
- | DefaultLanguage DefaultLanguage
- data LibraryField
- exposed :: Bool -> LibraryField
- exposedModules :: [NonEmptyString] -> LibraryField
- data ExecutableField
- data Executable = Executable {}
- executable :: NonEmptyString -> [ExecutableField] -> Section
- data TestSuiteType
- detailed :: TestSuiteField
- data TestSuiteField
- testModule :: NonEmptyString -> TestSuiteField
- data TestSuite = TestSuite {}
- testSuite :: NonEmptyString -> [TestSuiteField] -> Section
- data BenchmarkType = BenchExitCode
- data BenchmarkField
- data Benchmark = Benchmark {}
- benchmark :: NonEmptyString -> [BenchmarkField] -> Section
- class HasBuildInfo a where
- conditional :: CondBlock a -> a
- buildInfo :: BuildInfoField -> a
- buildDepends :: HasBuildInfo a => [Package] -> a
- otherModules :: HasBuildInfo a => [NonEmptyString] -> a
- hsSourceDirs :: HasBuildInfo a => [NonEmptyString] -> a
- extensions :: HasBuildInfo a => [NonEmptyString] -> a
- defaultExtensions :: HasBuildInfo a => [NonEmptyString] -> a
- otherExtensions :: HasBuildInfo a => [NonEmptyString] -> a
- buildTools :: HasBuildInfo a => [Package] -> a
- buildable :: HasBuildInfo a => Bool -> a
- ghcOptions :: HasBuildInfo a => [NonEmptyString] -> a
- ghcProfOptions :: HasBuildInfo a => [NonEmptyString] -> a
- ghcSharedOptions :: HasBuildInfo a => [NonEmptyString] -> a
- hugsOptions :: HasBuildInfo a => [NonEmptyString] -> a
- nhc98Options :: HasBuildInfo a => [NonEmptyString] -> a
- includes :: HasBuildInfo a => [NonEmptyString] -> a
- installIncludes :: HasBuildInfo a => [NonEmptyString] -> a
- includeDirs :: HasBuildInfo a => [NonEmptyString] -> a
- cSources :: HasBuildInfo a => [NonEmptyString] -> a
- extraLibraries :: HasBuildInfo a => [NonEmptyString] -> a
- extraLibDirs :: HasBuildInfo a => [NonEmptyString] -> a
- ccOptions :: HasBuildInfo a => [NonEmptyString] -> a
- cppOptions :: HasBuildInfo a => [NonEmptyString] -> a
- ldOptions :: HasBuildInfo a => [NonEmptyString] -> a
- pkgConfigDepends :: HasBuildInfo a => [Package] -> a
- frameworks :: HasBuildInfo a => [NonEmptyString] -> a
- class BuildsExe a where
- mainIs :: NonEmptyString -> a
- class BuildsExitcode a where
- exitcodeStdio :: a
- exitcodeFields :: (BuildsExitcode a, BuildsExe a) => NonEmptyString -> [a]
- modulesWithExtensions :: MonadIO m => [NonEmptyString] -> FilePath -> Betsy m [NonEmptyString]
- modules :: MonadIO m => FilePath -> Betsy m [NonEmptyString]
- fileExtensions :: [String]
- interestingFile :: [String] -> FilePath -> Bool
- interestingDir :: FilePath -> Bool
- modulesIO :: FilePath -> IO [String]
- modulesWithExtensionsIO :: [String] -> FilePath -> IO [String]
- sorter :: [String] -> [String] -> Ordering
- modulesInDir :: [String] -> FilePath -> [FilePath] -> IO [[String]]
- processFile :: [String] -> FilePath -> [FilePath] -> FilePath -> IO [[String]]
- data Section
- data BuildType
- simple :: BuildType
- custom :: BuildType
- make :: BuildType
- configure :: BuildType
- data License
- = GPL
- | AGPL
- | LGPL
- | BSD2
- | BSD3
- | BSD4
- | MIT
- | MPL
- | Apache
- | PublicDomain
- | AllRightsReserved
- | OtherLicense
- gpl :: License
- otherLicense :: License
- allRightsReserved :: License
- publicDomain :: License
- apache :: License
- mpl :: License
- mit :: License
- bsd4 :: License
- bsd3 :: License
- bsd2 :: License
- lgpl :: License
- agpl :: License
- data Compiler
- ghc :: Compiler
- lhc :: Compiler
- jhc :: Compiler
- helium :: Compiler
- hugs :: Compiler
- yhc :: Compiler
- nhc :: Compiler
- data Properties = Properties {
- name :: String
- version :: Version
- cabalVersion :: Maybe (Word, Word)
- buildType :: Maybe BuildType
- license :: Maybe License
- licenseFile :: String
- licenseFiles :: [NonEmptyString]
- copyright :: String
- author :: String
- maintainer :: String
- stability :: String
- homepage :: String
- bugReports :: String
- packageUrl :: String
- synopsis :: String
- description :: [String]
- category :: String
- testedWith :: [(Compiler, Constraint)]
- dataFiles :: [NonEmptyString]
- dataDir :: String
- extraSourceFiles :: [NonEmptyString]
- extraDocFiles :: [NonEmptyString]
- extraTmpFiles :: [NonEmptyString]
- data Cabal = Cabal {
- properties :: Properties
- library :: [LibraryField]
- sections :: [Section]
- flags :: [Flag]
Basic types
Blank
Typeclass for things that can be blank. More specifically,
blank a results in an item that, when rendered in a Cabal file,
is the null string. blank can be useful to indicate that you
have no options, and you can also use it in combination with record
syntax when you want to specify just a few options.
Instances
Repositories
What kind of VCS repository is this?
Version control systems.
Arguments
| :: NonEmptyString | The named module |
| -> Vcs |
data Repository Source
A single repository section.
Constructors
| Repository | |
Fields
| |
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
Condition; for use in a CondTree and ultimately in a
CondBlock, which implements Cabal's if-then-else feature.
Constructors
| OS NonEmptyString | Tests if the current operating system is the given name, case-insensitive |
| Arch NonEmptyString | Tests if the current architecture is the given name, case-insensitive |
| Impl Compiler Constraint | Tests for the configured Haskell implementation |
| CFlag FlagName | Evalutes to the current assignment of the flag of the given
name. To get a flag, use |
| CTrue | Always True |
| CFalse | Always False |
For use in a CondTree or ConstrTree.
Whether or equal to comparisions are also true.
data VersionComp Source
Expresses comparisons between versions.
Constructors
| LessThan OrEqualTo | |
| GreaterThan OrEqualTo | |
| EqualTo |
Instances
data ConstrTree Source
Expresses a tree of constraints. This is how you represent more complex dependency relationships.
Constructors
| Leaf VersionComp Version | |
| Branch Logical ConstrTree ConstrTree |
data Constraint Source
Expresses any version constraint, including no version constraint.
Constructors
| AnyVersion | |
| Constrained ConstrTree |
Conditions. Ultimately these are used in a CondBlock.
Conditional blocks. These implement the if-then-else feature
of Cabal files. You must have at least one thing to do if the
condition is True; the if-false block is optional.
Constructors
| CondBlock | |
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).
Arguments
| :: NonEmptyString | Package name |
| -> Version | Version number for lower bound |
| -> Version | Version number for upper bound |
| -> Package | Resulting |
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
Arguments
| :: NonEmptyString | Name of package |
| -> Package |
Allows any version of a package.
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]
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.
Versions
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.
Packages
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
. 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 unconstrained "QuickCheck"&&& and |||
combinators, to create your own Constraint and then use it with
the package function.
Constructors
| Package NonEmptyString Constraint |
Arguments
| :: NonEmptyString | The name of the package |
| -> Constraint | Version constraints. |
| -> Package |
Builds a Package.
Build information
data DefaultLanguage Source
Default language. Currently not documented, see
Constructors
| Haskell98 | |
| Haskell2010 |
haskell98 :: HasBuildInfo a => a Source
Sets Haskell 98 as the default-language.
Currently not documented in Cabal, see
haskell2010 :: HasBuildInfo a => a Source
Sets Haskell 2010 as the default-language.
Currently not documented in Cabal, see
data BuildInfoField Source
A single field of build information. This can appear in a
Library, Executable, TestSuite, or Benchmark.
Constructors
| BuildDepends [Package] | A list of packages needed to build this component |
| OtherModules [NonEmptyString] | 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
|
| HsSourceDirs [NonEmptyString] | Root directories for the module hierarchy |
| Extensions [NonEmptyString] | |
| DefaultExtensions [NonEmptyString] | |
| OtherExtensions [NonEmptyString] | |
| BuildTools [Package] | Programs needed to build this package, such as c2hs. |
| Buildable Bool | Is this component buildable? |
| GHCOptions [NonEmptyString] | |
| GHCProfOptions [NonEmptyString] | |
| GHCSharedOptions [NonEmptyString] | |
| HugsOptions [NonEmptyString] | |
| Nhc98Options [NonEmptyString] | |
| Includes [NonEmptyString] | 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 [NonEmptyString] | Header files to be installed into |
| IncludeDirs [NonEmptyString] | List of diretories to search for header files when dealing with C compilations. |
| CSources [NonEmptyString] | C sources to be compiled and lined with the Haskell files. |
| ExtraLibraries [NonEmptyString] | Extra libraries to link with. |
| ExtraLibDirs [NonEmptyString] | Directories to search for libraries. |
| CCOptions [NonEmptyString] | C Compiler options. |
| CPPOptions [NonEmptyString] | C Preprocessor options. Undocumented, see https://github.com/haskell/cabal/issues/646 |
| LDOptions [NonEmptyString] | Linker options. |
| PkgConfigDepends [Package] | List of pkg-config packages needed to build this component. |
| Frameworks [NonEmptyString] | OS X frameworks. |
| DefaultLanguage DefaultLanguage |
Instances
| Eq BuildInfoField | |
| Ord BuildInfoField | |
| Show BuildInfoField | |
| RenderableIndented BuildInfoField | 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. |
Libraries
data LibraryField Source
A field in the Library section of the Cabal file. A
Library section can have multiple fields.
Constructors
| ExposedModules [NonEmptyString] | Exposed modules. |
| Exposed Bool | Is the library exposed? GHC can hide libraries. |
| LibConditional (CondBlock LibraryField) | The |
| LibInfo BuildInfoField | The |
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
data ExecutableField Source
A single field in an Executable section. An Executable
section may have multiple fields.
Constructors
| ExeConditional (CondBlock ExecutableField) | An |
| ExeInfo BuildInfoField | An |
| ExeMainIs NonEmptyString | The name of the |
data Executable Source
An entire Executable section.
Constructors
| Executable | |
Fields
| |
Arguments
| :: NonEmptyString | The name of the executable that Cabal will build. |
| -> [ExecutableField] | An executable can contain zero or more |
| -> Section |
Builds a Section for executable files.
Test suites
data TestSuiteType Source
What kind of test suite is this?
Constructors
| ExitcodeStdio | An |
| Detailed | The |
data TestSuiteField Source
A single field value in a TestSuite section. A single test
suite section may contain mulitple fields.
Constructors
| TestConditional (CondBlock TestSuiteField) | The |
| TestInfo BuildInfoField | The |
| TestMainIs NonEmptyString | The name of the This is required when using |
| TestSuiteType TestSuiteType | |
| TestModule NonEmptyString | The module exporting the |
testModule :: NonEmptyString -> TestSuiteField Source
The module exporting the tests symbol. This is required when
using Detailed and disallowed when using ExitcodeStdio.
An entire test-suite section.
Constructors
| TestSuite | |
Fields
| |
Arguments
| :: NonEmptyString | The executable name for the resulting test suite |
| -> [TestSuiteField] | Zero or more |
| -> Section |
Builds a Section for test suites.
Benchmarks
data BenchmarkType Source
Constructors
| BenchExitCode |
|
data BenchmarkField Source
A single field in a Benchmark section.
Constructors
| BenchmarkConditional (CondBlock BenchmarkField) | |
| BenchmarkInfo BuildInfoField | |
| BenchmarkType BenchmarkType | |
| BenchmarkMainIs NonEmptyString | The name of the |
An entire Benchmark section.
Constructors
| Benchmark | |
Fields
| |
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.
Overloaded fields
class HasBuildInfo a where Source
Things that can be an item in a build information field in a Cabal file.
Methods
conditional :: CondBlock a -> a Source
Takes a conditional block and wraps it in the field type.
buildInfo :: BuildInfoField -> a Source
Takes a build information field and wraps it in the field type.
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?
ghcOptions :: HasBuildInfo a => [NonEmptyString] -> a Source
ghcProfOptions :: HasBuildInfo a => [NonEmptyString] -> a Source
ghcSharedOptions :: HasBuildInfo a => [NonEmptyString] -> a Source
hugsOptions :: HasBuildInfo a => [NonEmptyString] -> a Source
nhc98Options :: HasBuildInfo a => [NonEmptyString] -> a Source
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.
class BuildsExe a where Source
Sections that build executables. These are the Executable,
Benchmark, and TestSuite sections.
Methods
mainIs :: NonEmptyString -> a Source
Overloaded function allowing you to use mainIs for an
Executable, Benchmark, or TestSuite section.
class BuildsExitcode a where Source
Arguments
| :: (BuildsExitcode a, BuildsExe a) | |
| => NonEmptyString | Value for |
| -> [a] |
Builds two fields. The first indicates that this is an
exitcode-stdio-1.0 executable; the second is the appropriate
main-is field.
Getting module lists
Arguments
| :: MonadIO m | |
| => [NonEmptyString] | Look for files that have these extensions. 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.
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
interestingDir :: FilePath -> Bool Source
Arguments
| :: FilePath | Start searching within this directory. |
| -> IO [String] | 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. Only files
with one of the extensions listed in fileExtensions are
returned. 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.
modulesWithExtensionsIO Source
Arguments
| :: [String] | Look for files that have one of these extensions.
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. |
| -> IO [String] | 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.
Section
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.
Constructors
| SecRepo Repository | |
| SecExe Executable | |
| SecTest TestSuite | |
| SecBench Benchmark |
Properties
Constructors
| GPL | |
| AGPL | |
| LGPL | |
| BSD2 | |
| BSD3 | |
| BSD4 | |
| MIT | |
| MPL | |
| Apache | |
| PublicDomain | |
| AllRightsReserved | |
| OtherLicense |
Instances
data Properties Source
Global package properties.
Constructors
| Properties | |
Fields
| |