Safe Haskell | None |
---|---|
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)
- getAgdaAppDir :: IO 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 OptionsPragma = OptionsPragma {
- pragmaStrings :: [String]
- pragmaRange :: Range
- data AgdaLibFile = AgdaLibFile {
- _libName :: LibName
- _libFile :: FilePath
- _libAbove :: !Int
- _libIncludes :: [FilePath]
- _libDepends :: [LibName]
- _libPragmas :: OptionsPragma
- type ExeName = Text
- type LibM = ExceptT LibErrors (WriterT [LibWarning] (StateT LibState IO))
- mkLibM :: [AgdaLibFile] -> LibErrorIO a -> LibM a
- data LibWarning = LibWarning (Maybe LibPositionInfo) LibWarning'
- data LibPositionInfo = LibPositionInfo {
- libFilePos :: Maybe FilePath
- lineNumPos :: LineNumber
- filePos :: FilePath
- libraryWarningName :: LibWarning -> WarningName
- data ProjectConfig
- = ProjectConfig {
- configRoot :: FilePath
- configAgdaLibFiles :: [FilePath]
- configAbove :: !Int
- | DefaultProjectConfig
- = ProjectConfig {
- data VersionView = VersionView {}
- versionView :: LibName -> VersionView
- unVersionView :: VersionView -> LibName
- findLib' :: (a -> LibName) -> LibName -> [a] -> [a]
Documentation
findProjectRoot :: FilePath -> LibM (Maybe FilePath) Source #
Get project root
getAgdaAppDir :: IO FilePath Source #
Get the path to ~/.agda
(system-specific).
Can be overwritten by the AGDA_DIR
environment variable.
(This is not to be confused with the directory for the data files that Agda needs (e.g. the primitive modules).)
:: 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 OptionsPragma Source #
The options from an OPTIONS
pragma (or a .agda-lib
file).
In the future it might be nice to switch to a more structured representation. Note that, currently, there is not a one-to-one correspondence between list elements and options.
OptionsPragma | |
|
Instances
EmbPrj OptionsPragma Source # | |
Defined in Agda.TypeChecking.Serialise.Instances.Common icode :: OptionsPragma -> S Int32 Source # icod_ :: OptionsPragma -> S Int32 Source # value :: Int32 -> R OptionsPragma Source # | |
NFData OptionsPragma Source # | Ranges are not forced. |
Defined in Agda.Interaction.Library.Base rnf :: OptionsPragma -> () | |
Monoid OptionsPragma Source # | |
Defined in Agda.Interaction.Library.Base mappend :: OptionsPragma -> OptionsPragma -> OptionsPragma mconcat :: [OptionsPragma] -> OptionsPragma | |
Semigroup OptionsPragma Source # | |
Defined in Agda.Interaction.Library.Base (<>) :: OptionsPragma -> OptionsPragma -> OptionsPragma # sconcat :: NonEmpty OptionsPragma -> OptionsPragma stimes :: Integral b => b -> OptionsPragma -> OptionsPragma | |
Show OptionsPragma Source # | |
Defined in Agda.Interaction.Library.Base showsPrec :: Int -> OptionsPragma -> ShowS show :: OptionsPragma -> String showList :: [OptionsPragma] -> ShowS |
data AgdaLibFile Source #
Content of a .agda-lib
file.
AgdaLibFile | |
|
Instances
NFData AgdaLibFile Source # | |||||
Defined in Agda.Interaction.Library.Base rnf :: AgdaLibFile -> () | |||||
Generic AgdaLibFile Source # | |||||
Defined in Agda.Interaction.Library.Base
from :: AgdaLibFile -> Rep AgdaLibFile x to :: Rep AgdaLibFile x -> AgdaLibFile | |||||
Show AgdaLibFile Source # | |||||
Defined in Agda.Interaction.Library.Base showsPrec :: Int -> AgdaLibFile -> ShowS show :: AgdaLibFile -> String showList :: [AgdaLibFile] -> ShowS | |||||
type Rep AgdaLibFile Source # | |||||
Defined in Agda.Interaction.Library.Base type Rep AgdaLibFile = D1 ('MetaData "AgdaLibFile" "Agda.Interaction.Library.Base" "Agda-2.6.20240714-inplace" 'False) (C1 ('MetaCons "AgdaLibFile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_libName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibName) :*: (S1 ('MetaSel ('Just "_libFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "_libAbove") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "_libIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "_libDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LibName]) :*: S1 ('MetaSel ('Just "_libPragmas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptionsPragma))))) |
type LibM = ExceptT LibErrors (WriterT [LibWarning] (StateT LibState IO)) Source #
Throws LibErrors
exceptions, still collects LibWarning
s.
mkLibM :: [AgdaLibFile] -> LibErrorIO a -> LibM a Source #
Raise collected LibErrors
as exception.
data LibWarning Source #
Instances
Pretty LibWarning Source # | |||||
Defined in Agda.Interaction.Library.Base pretty :: LibWarning -> Doc Source # prettyPrec :: Int -> LibWarning -> Doc Source # prettyList :: [LibWarning] -> Doc Source # | |||||
EmbPrj LibWarning Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors icode :: LibWarning -> S Int32 Source # icod_ :: LibWarning -> S Int32 Source # value :: Int32 -> R LibWarning Source # | |||||
NFData LibWarning Source # | |||||
Defined in Agda.Interaction.Library.Base rnf :: LibWarning -> () | |||||
Generic LibWarning Source # | |||||
Defined in Agda.Interaction.Library.Base
from :: LibWarning -> Rep LibWarning x to :: Rep LibWarning x -> LibWarning | |||||
Show LibWarning Source # | |||||
Defined in Agda.Interaction.Library.Base showsPrec :: Int -> LibWarning -> ShowS show :: LibWarning -> String showList :: [LibWarning] -> ShowS | |||||
type Rep LibWarning Source # | |||||
Defined in Agda.Interaction.Library.Base type Rep LibWarning = D1 ('MetaData "LibWarning" "Agda.Interaction.Library.Base" "Agda-2.6.20240714-inplace" 'False) (C1 ('MetaCons "LibWarning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LibPositionInfo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibWarning'))) |
data LibPositionInfo Source #
Information about which .agda-lib
file we are reading
and from where in the libraries
file it came from.
LibPositionInfo | |
|
Instances
EmbPrj LibPositionInfo Source # | |||||
Defined in Agda.TypeChecking.Serialise.Instances.Errors icode :: LibPositionInfo -> S Int32 Source # icod_ :: LibPositionInfo -> S Int32 Source # value :: Int32 -> R LibPositionInfo Source # | |||||
NFData LibPositionInfo Source # | |||||
Defined in Agda.Interaction.Library.Base rnf :: LibPositionInfo -> () | |||||
Generic LibPositionInfo Source # | |||||
Defined in Agda.Interaction.Library.Base
from :: LibPositionInfo -> Rep LibPositionInfo x to :: Rep LibPositionInfo x -> LibPositionInfo | |||||
Show LibPositionInfo Source # | |||||
Defined in Agda.Interaction.Library.Base showsPrec :: Int -> LibPositionInfo -> ShowS show :: LibPositionInfo -> String showList :: [LibPositionInfo] -> ShowS | |||||
type Rep LibPositionInfo Source # | |||||
Defined in Agda.Interaction.Library.Base type Rep LibPositionInfo = D1 ('MetaData "LibPositionInfo" "Agda.Interaction.Library.Base" "Agda-2.6.20240714-inplace" 'False) (C1 ('MetaCons "LibPositionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "libFilePos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "lineNumPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineNumber) :*: S1 ('MetaSel ('Just "filePos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) |
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.
ProjectConfig | |
| |
DefaultProjectConfig |
Instances
NFData ProjectConfig Source # | |||||
Defined in Agda.Interaction.Library.Base rnf :: ProjectConfig -> () | |||||
Generic ProjectConfig Source # | |||||
Defined in Agda.Interaction.Library.Base
from :: ProjectConfig -> Rep ProjectConfig x to :: Rep ProjectConfig x -> ProjectConfig | |||||
type Rep ProjectConfig Source # | |||||
Defined in Agda.Interaction.Library.Base type Rep ProjectConfig = D1 ('MetaData "ProjectConfig" "Agda.Interaction.Library.Base" "Agda-2.6.20240714-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]) :*: S1 ('MetaSel ('Just "configAbove") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :+: 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" ] == []