scion-0.1.0.1: Haskell IDE librarySource codeContentsIndex
Scion.Types.Notes
Portabilityportable
Stabilityexperimental
Maintainernominolo@googlemail.com
Description
Notes, i.e., warnings, errors, etc.
Synopsis
data Location
data LocSource
= FileSrc AbsFilePath
| OtherSrc String
mkLocation :: LocSource -> Int -> Int -> Int -> Int -> Location
mkNoLoc :: String -> Location
locSource :: Location -> LocSource
isValidLoc :: Location -> Bool
noLocText :: Location -> String
viewLoc :: Location -> (LocSource, Int, Int, Int, Int)
locStartCol :: Location -> Int
locEndCol :: Location -> Int
locStartLine :: Location -> Int
locEndLine :: Location -> Int
data AbsFilePath
mkAbsFilePath :: FilePath -> FilePath -> AbsFilePath
data Note = Note {
noteKind :: NoteKind
noteLoc :: Location
noteMessage :: String
}
data NoteKind
= ErrorNote
| WarningNote
| InfoNote
| OtherNote
type Notes = MultiSet Note
ghcSpanToLocation :: FilePath -> SrcSpan -> Location
ghcErrMsgToNote :: FilePath -> ErrMsg -> Note
ghcWarnMsgToNote :: FilePath -> WarnMsg -> Note
ghcMessagesToNotes :: FilePath -> Messages -> Notes
Documentation
data Location Source

Scion's type for source code locations (regions).

We use a custom location type for two reasons:

1. We enforce the invariant, that the file path of the location is an absolute path.

2. Independent evolution from the GHC API.

To save space, the Location type is kept abstract and uses special cases for notes that span only one line or are only one character wide. Use mkLocation and viewLoc as well as the respective accessor functions to construct and destruct nodes.

If no reasonable can be given, use the mkNoLoc function, but be careful not to call viewLoc or any other accessor function on such a Location.

show/hide Instances
data LocSource Source
The "source" of a location.
Constructors
FileSrc AbsFilePathThe location refers to a position in a file.
OtherSrc StringThe location refers to something else, e.g., the command line, or stdin.
show/hide Instances
mkLocationSource
:: LocSource
-> Intstart line
-> Intstart column
-> Intend line
-> Intend column
-> Location

Construct a source code location from start and end point.

If the start point is after the end point, they are swapped automatically.

mkNoLoc :: String -> LocationSource
Construct a source location that does not specify a region. The argument can be used to give some hint as to why there is no location available. (E.g., "File not found").
locSource :: Location -> LocSourceSource
isValidLoc :: Location -> BoolSource
Test whether a location is valid, i.e., not constructed with mkNoLoc.
noLocText :: Location -> StringSource
viewLocSource
:: Location
-> (LocSource, Int, Int, Int, Int)source, start line, start column, end line, end column.

View on a (valid) location.

It holds the property:

 prop_viewLoc_mkLoc s l0 c0 l1 c1 =
     viewLoc (mkLocation s l0 c0 l1 c1) == (s, l0, c0, l1, c1)
locStartCol :: Location -> IntSource
Return the start column. Only defined on valid locations.
locEndCol :: Location -> IntSource
Return the end column. Only defined on valid locations.
locStartLine :: Location -> IntSource
Return the start line. Only defined on valid locations.
locEndLine :: Location -> IntSource
Return the end line. Only defined on valid locations.
data AbsFilePath Source

Represents a FilePath which we know is absolute.

Since relative FilePaths depend on the a current working directory we normalise all paths to absolute paths. Use mkAbsFilePath to create absolute file paths.

show/hide Instances
mkAbsFilePathSource
:: FilePathbase directory (must be absolute)
-> FilePathabsolute or relative
-> AbsFilePath

Create an absolute file path given a base directory.

Throws an error if the first argument is not an absolute path.

data Note Source
A note from the compiler or some other tool.
Constructors
Note
noteKind :: NoteKind
noteLoc :: Location
noteMessage :: String
show/hide Instances
data NoteKind Source
Classifies the kind (or severity) of a note.
Constructors
ErrorNote
WarningNote
InfoNote
OtherNote
show/hide Instances
type Notes = MultiSet NoteSource
ghcSpanToLocationSource
:: FilePathBase directory
-> SrcSpan
-> Location

Convert a SrcSpan to a Location.

The first argument is used to normalise relative source locations to an absolute file path.

ghcErrMsgToNote :: FilePath -> ErrMsg -> NoteSource
ghcWarnMsgToNote :: FilePath -> WarnMsg -> NoteSource
ghcMessagesToNotesSource
:: FilePathBase path for normalising paths. See mkAbsFilePath.
-> Messages
-> Notes

Convert Messages to Notes.

This will mix warnings and errors, but you can split them back up by filtering the Notes based on the noteKind.

Produced by Haddock version 2.4.2