Copyright | (c) Fontaine 2008 - 2011 |
---|---|
License | BSD3 |
Maintainer | Fontaine@cs.uni-duesseldorf.de |
Stability | experimental |
Portability | GHC-only |
Safe Haskell | None |
Language | Haskell2010 |
Frontend contains some reexports from other modules
- parse :: SourceName -> [Token] -> Either ParseError ModuleFromParser
- data ParseError = ParseError {}
- parseFile :: FilePath -> IO ModuleFromParser
- benchmarkFrontend :: FilePath -> IO (ModuleFromParser, ModuleFromRenaming)
- eitherToExc :: Exception a => Either a b -> IO b
- handleLexError :: (LexError -> IO a) -> IO a -> IO a
- handleParseError :: (ParseError -> IO a) -> IO a -> IO a
- handleRenameError :: (RenameError -> IO a) -> IO a -> IO a
- data Token
- data LexError = LexError {}
- lexInclude :: String -> IO (Either LexError [Token])
- lexPlain :: String -> Either LexError [Token]
- removeIgnoredToken :: [Token] -> [Token]
- data Module a
- type ModuleFromParser = Module FromParser
- type ModuleFromRenaming = Module FromRenaming
- data Labeled t = Labeled {}
- castModule :: Module a -> Module b
- type Bindings = Map String UniqueIdent
- data SrcLoc
- = TokIdPos TokenId
- | TokIdSpan TokenId TokenId
- | TokSpan Token Token
- | TokPos Token
- | NoLocation
- | FixedLoc {
- fixedStartLine :: !Int
- fixedStartCol :: !Int
- fixedStartOffset :: !Int
- fixedLen :: !Int
- fixedEndLine :: !Int
- fixedEndCol :: !Int
- fixedEndOffset :: !Int
- renameModule :: ModuleFromParser -> Either RenameError (ModuleFromRenaming, RenameInfo)
- data RenameInfo = RenameInfo {}
- data RenameError = RenameError {}
- removeSourceLocations :: Data a => a -> a
- removeParens :: Data a => a -> a
- unUniqueIdent :: Data a => a -> a
- computeFreeNames :: Data a => a -> FreeNames
- setNodeIdsZero :: Data a => a -> a
- frontendVersion :: Version
Documentation
parse :: SourceName -> [Token] -> Either ParseError ModuleFromParser Source #
The parse
function parses a List of Token
.
It returns a ParseError
or a Labled
Module
.
The SourceName
argument is currently not used.
data ParseError Source #
ParseError data type. This is an instance of Excpetion
parseFile :: FilePath -> IO ModuleFromParser Source #
Lex and parse a file and return a LModule, throw an exception in case of an error
benchmarkFrontend :: FilePath -> IO (ModuleFromParser, ModuleFromRenaming) Source #
Lex and parse File. | Return the module and print some timing infos
eitherToExc :: Exception a => Either a b -> IO b Source #
"eitherToExe" returns the Right part of Either or throws the Left part as an dynamic exception.
handleLexError :: (LexError -> IO a) -> IO a -> IO a Source #
Handle a dymanic exception of type LexError.
handleParseError :: (ParseError -> IO a) -> IO a -> IO a Source #
Handle a dymanic exception of type ParseError.
handleRenameError :: (RenameError -> IO a) -> IO a -> IO a Source #
Handle a dymanic exception of type RenameError.
lexInclude :: String -> IO (Either LexError [Token]) Source #
lex input-string and inport all includes files
removeIgnoredToken :: [Token] -> [Token] Source #
Remove comments, whitespaces and unneeded newlines.
type ModuleFromParser = Module FromParser Source #
type ModuleFromRenaming = Module FromRenaming Source #
A module that has gone through renaming
castModule :: Module a -> Module b Source #
TokIdPos TokenId | |
TokIdSpan TokenId TokenId | |
TokSpan Token Token | |
TokPos Token | |
NoLocation | |
FixedLoc | |
|
renameModule :: ModuleFromParser -> Either RenameError (ModuleFromRenaming, RenameInfo) Source #
renameModule
renames a Module
.
| (also calls mergeFunBinds)
data RenameError Source #
removeSourceLocations :: Data a => a -> a Source #
removeSourceLocations
sets all locationsInfos to NoLocation
removeParens :: Data a => a -> a Source #
removeParens
removes all occurences of of Parens,
i.e. explicit parentheses from the AST
unUniqueIdent :: Data a => a -> a Source #
unUniqueIdent replaces the all UIdent with the Ident of the the new name, thus forgetting additional information like the bindingside, etc. Usefull to get a smaller AST.
computeFreeNames :: Data a => a -> FreeNames Source #
Compute the FreeNames of an Expression. This function does only work after renaming has been done. This implementation is inefficient.
setNodeIdsZero :: Data a => a -> a Source #
Set all NodeIds to zero.
frontendVersion :: Version Source #
The version of the CSPM-Frontend library