Agda-2.7.0: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Interaction.Library.Base

Description

Basic data types for library management.

Synopsis

Documentation

type LibName = String Source #

A symbolic library name.

data LibrariesFile Source #

Constructors

LibrariesFile 

Fields

  • lfPath :: FilePath

    E.g. ~.agdalibraries.

  • lfExists :: Bool

    The libraries file might not exist, but we may print its assumed location in error messages.

Instances

Instances details
Generic LibrariesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibrariesFile :: Type -> Type #

Show LibrariesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibrariesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibrariesFile -> () #

type Rep LibrariesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibrariesFile = D1 ('MetaData "LibrariesFile" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (C1 ('MetaCons "LibrariesFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "lfPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "lfExists") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

type ExeName = Text Source #

A symbolic executable name.

data ExecutablesFile Source #

Constructors

ExecutablesFile 

Fields

  • efPath :: FilePath

    E.g. ~.agdaexecutables.

  • efExists :: Bool

    The executables file might not exist, but we may print its assumed location in error messages.

Instances

Instances details
EmbPrj ExecutablesFile Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Errors

Generic ExecutablesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep ExecutablesFile :: Type -> Type #

Show ExecutablesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData ExecutablesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: ExecutablesFile -> () #

type Rep ExecutablesFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep ExecutablesFile = D1 ('MetaData "ExecutablesFile" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (C1 ('MetaCons "ExecutablesFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "efPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "efExists") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

libNameForCurrentDir :: LibName Source #

The special name "." is used to indicated that the current directory should count as a project root.

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.

Constructors

ProjectConfig 

Fields

DefaultProjectConfig 

Instances

Instances details
Generic ProjectConfig Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep ProjectConfig :: Type -> Type #

NFData ProjectConfig Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: ProjectConfig -> () #

type Rep ProjectConfig Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep ProjectConfig = D1 ('MetaData "ProjectConfig" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" '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))

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.

Constructors

OptionsPragma 

Fields

data AgdaLibFile Source #

Content of a .agda-lib file.

Constructors

AgdaLibFile 

Fields

Instances

Instances details
Generic AgdaLibFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep AgdaLibFile :: Type -> Type #

Show AgdaLibFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData AgdaLibFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: AgdaLibFile -> () #

type Rep AgdaLibFile Source # 
Instance details

Defined in Agda.Interaction.Library.Base

libName :: Lens' AgdaLibFile LibName Source #

Lenses for AgdaLibFile

Library warnings and errors

Position information

data LibPositionInfo Source #

Information about which .agda-lib file we are reading and from where in the libraries file it came from.

Constructors

LibPositionInfo 

Fields

Warnings

data LibWarning Source #

Instances

Instances details
Pretty LibWarning Source # 
Instance details

Defined in Agda.Interaction.Library.Base

EmbPrj LibWarning Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Errors

Generic LibWarning Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibWarning :: Type -> Type #

Show LibWarning Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibWarning Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibWarning -> () #

type Rep LibWarning Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibWarning = D1 ('MetaData "LibWarning" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" '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 LibWarning' Source #

Library Warnings.

Constructors

UnknownField String 

Instances

Instances details
Pretty LibWarning' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

EmbPrj LibWarning' Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Errors

Generic LibWarning' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibWarning' :: Type -> Type #

Show LibWarning' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibWarning' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibWarning' -> () #

type Rep LibWarning' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibWarning' = D1 ('MetaData "LibWarning'" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (C1 ('MetaCons "UnknownField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Errors

data LibError Source #

Instances

Instances details
Generic LibError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibError :: Type -> Type #

Methods

from :: LibError -> Rep LibError x #

to :: Rep LibError x -> LibError #

Show LibError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibError -> () #

type Rep LibError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibError = D1 ('MetaData "LibError" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (C1 ('MetaCons "LibError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LibPositionInfo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibError')))

data LibError' Source #

Collected errors while processing library files.

Constructors

LibrariesFileNotFound FilePath

The user specified replacement for the default libraries file does not exist.

LibNotFound LibrariesFile LibName

Raised when a library name could not successfully be resolved to an .agda-lib file.

AmbiguousLib LibName [AgdaLibFile]

Raised when a library name is defined in several .agda-lib files.

LibParseError LibParseError

The .agda-lib file could not be parsed.

ReadError

An I/O Error occurred when reading a file.

Fields

DuplicateExecutable

The executables file contains duplicate entries.

Fields

Instances

Instances details
Pretty LibError' Source #

Pretty-print library management error without position info.

Instance details

Defined in Agda.Interaction.Library.Base

Generic LibError' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibError' :: Type -> Type #

Show LibError' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibError' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibError' -> () #

type Rep LibError' Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibError' = D1 ('MetaData "LibError'" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) ((C1 ('MetaCons "LibrariesFileNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: (C1 ('MetaCons "LibNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibrariesFile) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibName)) :+: C1 ('MetaCons "AmbiguousLib" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AgdaLibFile])))) :+: (C1 ('MetaCons "LibParseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibParseError)) :+: (C1 ('MetaCons "ReadError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IOException) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "DuplicateExecutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List2 (LineNumber, FilePath))))))))

data LibParseError Source #

Exceptions thrown by the .agda-lib parser.

Constructors

BadLibraryName String

An invalid library name, e.g., containing spaces.

ReadFailure FilePath IOException

I/O error while reading file.

MissingFields (List1 String)

Missing these mandatory fields.

DuplicateFields (List1 String)

These fields occur each more than once.

MissingFieldName LineNumber

At the given line number, a field name is missing before the :.

BadFieldName LineNumber String

At the given line number, an invalid field name is encountered before the :. (E.g., containing spaces.)

MissingColonForField LineNumber String

At the given line number, the given field is not followed by :.

ContentWithoutField LineNumber

At the given line number, indented text (content) is not preceded by a field.

Instances

Instances details
Pretty LibParseError Source #

Print library file parse error without position info.

Instance details

Defined in Agda.Interaction.Library.Base

Generic LibParseError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibParseError :: Type -> Type #

Show LibParseError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibParseError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibParseError -> () #

type Rep LibParseError Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibParseError = D1 ('MetaData "LibParseError" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (((C1 ('MetaCons "BadLibraryName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ReadFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IOException))) :+: (C1 ('MetaCons "MissingFields" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 String))) :+: C1 ('MetaCons "DuplicateFields" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 String))))) :+: ((C1 ('MetaCons "MissingFieldName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineNumber)) :+: C1 ('MetaCons "BadFieldName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineNumber) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "MissingColonForField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineNumber) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ContentWithoutField" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineNumber)))))

Raising warnings and errors

Library Monad

type LibM = ExceptT LibErrors (WriterT [LibWarning] (StateT LibState IO)) Source #

Throws LibErrors exceptions, still collects LibWarnings.

type LibState = (Map FilePath ProjectConfig, Map FilePath AgdaLibFile) Source #

Cache locations of project configurations and parsed .agda-lib files.

data LibErrors Source #

Collected errors when processing an .agda-lib file.

Instances

Instances details
Generic LibErrors Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Associated Types

type Rep LibErrors :: Type -> Type #

Show LibErrors Source # 
Instance details

Defined in Agda.Interaction.Library.Base

NFData LibErrors Source # 
Instance details

Defined in Agda.Interaction.Library.Base

Methods

rnf :: LibErrors -> () #

type Rep LibErrors Source # 
Instance details

Defined in Agda.Interaction.Library.Base

type Rep LibErrors = D1 ('MetaData "LibErrors" "Agda.Interaction.Library.Base" "Agda-2.7.0-GLfwtYnpcYgL7izVkqfuSR" 'False) (C1 ('MetaCons "LibErrors" 'PrefixI 'True) (S1 ('MetaSel ('Just "libErrorsInstalledLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AgdaLibFile]) :*: S1 ('MetaSel ('Just "libErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 LibError))))

Prettyprinting errors and warnings

hasLineNumber :: LibParseError -> Maybe LineNumber Source #

Does a parse error contain a line number?

formatLibPositionInfo :: LibPositionInfo -> LibParseError -> Doc Source #

Compute a position position prefix.

Depending on the error to be printed, it will

  • either give the name of the libraries file and a line inside it,
  • or give the name of the .agda-lib file.

Orphan instances

NFData IOException Source # 
Instance details

Methods

rnf :: IOException -> () #