Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Library management.
Sample use:
-- Get libraries as listed in.agda/libraries
file. libs <- getInstalledLibraries Nothing -- Get the libraries (and immediate paths) relevant forprojectRoot
. -- This involves locating and processing the.agda-lib
file for the project. (libNames, includePaths) <- getDefaultLibraries projectRoot True -- Get include paths of depended-on libraries. resolvedPaths <- libraryIncludePaths Nothing libs libNames let allPaths = includePaths ++ resolvedPaths
Synopsis
- findProjectRoot :: FilePath -> LibM (Maybe FilePath)
- getDefaultLibraries :: FilePath -> Bool -> LibM ([LibName], [FilePath])
- getInstalledLibraries :: Maybe FilePath -> LibM [AgdaLibFile]
- getTrustedExecutables :: LibM (Map ExeName FilePath)
- libraryIncludePaths :: Maybe FilePath -> [AgdaLibFile] -> [LibName] -> LibM [FilePath]
- getAgdaLibFiles' :: FilePath -> LibErrorIO [AgdaLibFile]
- getPrimitiveLibDir :: IO FilePath
- type LibName = String
- data AgdaLibFile = AgdaLibFile {
- _libName :: LibName
- _libFile :: FilePath
- _libIncludes :: [FilePath]
- _libDepends :: [LibName]
- _libPragmas :: [String]
- type ExeName = Text
- type LibM = ExceptT Doc (WriterT [LibWarning] (StateT LibState IO))
- mkLibM :: [AgdaLibFile] -> LibErrorIO a -> LibM a
- data LibWarning = LibWarning (Maybe LibPositionInfo) LibWarning'
- data LibPositionInfo = LibPositionInfo {}
- libraryWarningName :: LibWarning -> WarningName
- data ProjectConfig
- data VersionView = VersionView {}
- versionView :: LibName -> VersionView
- unVersionView :: VersionView -> LibName
- findLib' :: (a -> LibName) -> LibName -> [a] -> [a]
Documentation
:: FilePath | Project root. |
-> Bool | Use |
-> LibM ([LibName], [FilePath]) | The returned |
Get dependencies and include paths for given project root:
Look for .agda-lib
files according to findAgdaLibFiles
.
If none are found, use default dependencies (according to defaults
file)
and current directory (project root).
getInstalledLibraries Source #
:: Maybe FilePath | Override the default |
-> LibM [AgdaLibFile] | Content of library files. (Might have empty |
Parse the descriptions of the libraries Agda knows about.
Returns none if there is no libraries
file.
getTrustedExecutables Source #
Return the trusted executables Agda knows about.
Returns none if there is no executables
file.
:: Maybe FilePath |
|
-> [AgdaLibFile] | Libraries Agda knows about. |
-> [LibName] | (Non-empty) library names to be resolved to (lists of) pathes. |
-> LibM [FilePath] | Resolved pathes (no duplicates). Contains "." if |
Get all include pathes for a list of libraries to use.
getAgdaLibFiles' :: FilePath -> LibErrorIO [AgdaLibFile] Source #
Get the contents of .agda-lib
files in the given project root.
getPrimitiveLibDir :: IO FilePath Source #
Returns the absolute default lib dir. This directory is used to store the Primitive.agda file.
data AgdaLibFile Source #
Content of a .agda-lib
file.
AgdaLibFile | |
|
Instances
type LibM = ExceptT Doc (WriterT [LibWarning] (StateT LibState IO)) Source #
Throws Doc
exceptions, still collects LibWarning
s.
mkLibM :: [AgdaLibFile] -> LibErrorIO a -> LibM a Source #
Raise collected LibErrors
as exception.
data LibWarning Source #
Instances
data LibPositionInfo Source #
LibPositionInfo | |
|
Instances
data ProjectConfig Source #
A file can either belong to a project located at a given root containing one or more .agda-lib files, or be part of the default project.
Instances
Generic ProjectConfig Source # | |
Defined in Agda.Interaction.Library.Base type Rep ProjectConfig :: Type -> Type # from :: ProjectConfig -> Rep ProjectConfig x # to :: Rep ProjectConfig x -> ProjectConfig # | |
NFData ProjectConfig Source # | |
Defined in Agda.Interaction.Library.Base rnf :: ProjectConfig -> () # | |
type Rep ProjectConfig Source # | |
Defined in Agda.Interaction.Library.Base type Rep ProjectConfig = D1 ('MetaData "ProjectConfig" "Agda.Interaction.Library.Base" "Agda-2.6.2.1-inplace" 'False) (C1 ('MetaCons "ProjectConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "configRoot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "configAgdaLibFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :+: C1 ('MetaCons "DefaultProjectConfig" 'PrefixI 'False) (U1 :: Type -> Type)) |
Exported for testing
data VersionView Source #
Library names are structured into the base name and a suffix of version
numbers, e.g. mylib-1.2.3
. The version suffix is optional.
Instances
Show VersionView Source # | |
Defined in Agda.Interaction.Library showsPrec :: Int -> VersionView -> ShowS # show :: VersionView -> String # showList :: [VersionView] -> ShowS # | |
Eq VersionView Source # | |
Defined in Agda.Interaction.Library (==) :: VersionView -> VersionView -> Bool # (/=) :: VersionView -> VersionView -> Bool # |
versionView :: LibName -> VersionView Source #
Split a library name into basename and a list of version numbers.
versionView "foo-1.2.3" == VersionView "foo" [1, 2, 3] versionView "foo-01.002.3" == VersionView "foo" [1, 2, 3]
Note that because of leading zeros, versionView
is not injective.
(unVersionView . versionView
would produce a normal form.)
unVersionView :: VersionView -> LibName Source #
Print a VersionView
, inverse of versionView
(modulo leading zeros).
findLib' :: (a -> LibName) -> LibName -> [a] -> [a] Source #
Generalized version of findLib
for testing.
findLib' id "a" [ "a-1", "a-02", "a-2", "b" ] == [ "a-02", "a-2" ]
findLib' id "a" [ "a", "a-1", "a-01", "a-2", "b" ] == [ "a" ] findLib' id "a-1" [ "a", "a-1", "a-01", "a-2", "b" ] == [ "a-1", "a-01" ] findLib' id "a-2" [ "a", "a-1", "a-01", "a-2", "b" ] == [ "a-2" ] findLib' id "c" [ "a", "a-1", "a-01", "a-2", "b" ] == []