Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Basic data types for library management.
Synopsis
- type LibName = String
- data LibrariesFile = LibrariesFile {}
- type ExeName = Text
- data ExecutablesFile = ExecutablesFile {}
- libNameForCurrentDir :: LibName
- data ProjectConfig
- data AgdaLibFile = AgdaLibFile {
- _libName :: LibName
- _libFile :: FilePath
- _libIncludes :: [FilePath]
- _libDepends :: [LibName]
- _libPragmas :: [String]
- emptyLibFile :: AgdaLibFile
- libName :: Lens' LibName AgdaLibFile
- libFile :: Lens' FilePath AgdaLibFile
- libIncludes :: Lens' [FilePath] AgdaLibFile
- libDepends :: Lens' [LibName] AgdaLibFile
- libPragmas :: Lens' [String] AgdaLibFile
- type LineNumber = Int
- data LibPositionInfo = LibPositionInfo {}
- data LibWarning = LibWarning (Maybe LibPositionInfo) LibWarning'
- data LibWarning' = UnknownField String
- data LibError = LibError (Maybe LibPositionInfo) LibError'
- libraryWarningName :: LibWarning -> WarningName
- data LibError'
- type LibState = (Map FilePath ProjectConfig, Map FilePath AgdaLibFile)
- type LibErrorIO = WriterT [Either LibError LibWarning] (StateT LibState IO)
- type LibM = ExceptT Doc (WriterT [LibWarning] (StateT LibState IO))
- warnings :: MonadWriter [Either LibError LibWarning] m => [LibWarning] -> m ()
- warnings' :: MonadWriter [Either LibError LibWarning] m => [LibWarning'] -> m ()
- raiseErrors' :: MonadWriter [Either LibError LibWarning] m => [LibError'] -> m ()
- raiseErrors :: MonadWriter [Either LibError LibWarning] m => [LibError] -> m ()
- getCachedProjectConfig :: (MonadState LibState m, MonadIO m) => FilePath -> m (Maybe ProjectConfig)
- storeCachedProjectConfig :: (MonadState LibState m, MonadIO m) => FilePath -> ProjectConfig -> m ()
- getCachedAgdaLibFile :: (MonadState LibState m, MonadIO m) => FilePath -> m (Maybe AgdaLibFile)
- storeCachedAgdaLibFile :: (MonadState LibState m, MonadIO m) => FilePath -> AgdaLibFile -> m ()
- formatLibPositionInfo :: LibPositionInfo -> String -> Doc
- formatLibError :: [AgdaLibFile] -> LibError -> Doc
Documentation
data LibrariesFile Source #
Instances
Show LibrariesFile Source # | |
Defined in Agda.Interaction.Library.Base showsPrec :: Int -> LibrariesFile -> ShowS # show :: LibrariesFile -> String # showList :: [LibrariesFile] -> ShowS # |
data ExecutablesFile Source #
Instances
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.
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.20220320-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)) |
data AgdaLibFile Source #
Content of a .agda-lib
file.
AgdaLibFile | |
|
Instances
libDepends :: Lens' [LibName] AgdaLibFile Source #
libPragmas :: Lens' [String] AgdaLibFile Source #
Library warnings and errors
type LineNumber = Int Source #
data LibPositionInfo Source #
LibPositionInfo | |
|
Instances
data LibWarning Source #
Instances
data LibWarning' Source #
Library Warnings.
Instances
Collected errors while processing library files.
LibNotFound LibrariesFile LibName | Raised when a library name could not successfully be resolved
to an |
AmbiguousLib LibName [AgdaLibFile] | Raised when a library name is defined in several |
OtherError String | Generic error. |
type LibState = (Map FilePath ProjectConfig, Map FilePath AgdaLibFile) Source #
Cache locations of project configurations and parsed .agda-lib files
type LibErrorIO = WriterT [Either LibError LibWarning] (StateT LibState IO) Source #
Collects LibError
s and LibWarning
s.
type LibM = ExceptT Doc (WriterT [LibWarning] (StateT LibState IO)) Source #
Throws Doc
exceptions, still collects LibWarning
s.
warnings :: MonadWriter [Either LibError LibWarning] m => [LibWarning] -> m () Source #
warnings' :: MonadWriter [Either LibError LibWarning] m => [LibWarning'] -> m () Source #
raiseErrors' :: MonadWriter [Either LibError LibWarning] m => [LibError'] -> m () Source #
raiseErrors :: MonadWriter [Either LibError LibWarning] m => [LibError] -> m () Source #
getCachedProjectConfig :: (MonadState LibState m, MonadIO m) => FilePath -> m (Maybe ProjectConfig) Source #
storeCachedProjectConfig :: (MonadState LibState m, MonadIO m) => FilePath -> ProjectConfig -> m () Source #
getCachedAgdaLibFile :: (MonadState LibState m, MonadIO m) => FilePath -> m (Maybe AgdaLibFile) Source #
storeCachedAgdaLibFile :: (MonadState LibState m, MonadIO m) => FilePath -> AgdaLibFile -> m () Source #
Prettyprinting errors and warnings
formatLibPositionInfo :: LibPositionInfo -> String -> Doc Source #
formatLibError :: [AgdaLibFile] -> LibError -> Doc Source #
Pretty-print LibError
.