| Portability | GHC-only |
|---|---|
| Stability | experimental |
| Maintainer | Fontaine@cs.uni-duesseldorf.de |
Language.CSPM.Frontend
Description
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]
- filterIgnoredToken :: [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 {}
- getRenaming :: ModuleFromParser -> Either RenameError (Bindings, AstAnnotation UniqueIdent, AstAnnotation UniqueIdent)
- applyRenaming :: (Bindings, AstAnnotation UniqueIdent, AstAnnotation UniqueIdent) -> ModuleFromParser -> ModuleFromRenaming
- data RenameError = RenameError {}
- removeSourceLocations :: Data a => Labeled (Module a) -> Labeled (Module a)
- removeParens :: Data a => Labeled (Module a) -> Labeled (Module a)
- removeModuleTokens :: Labeled (Module a) -> Labeled (Module a)
- unUniqueIdent :: Data a => Labeled (Module a) -> Labeled (Module a)
- showAst :: Data a => Labeled a -> String
- computeFreeNames :: Data a => a -> FreeNames
- setNodeIdsZero :: Data a => Labeled (Module a) -> Labeled (Module a)
- pp :: PP x => x -> Doc
- prettyPrintFile :: FilePath -> IO ()
Documentation
parse :: SourceName -> [Token] -> Either ParseError ModuleFromParserSource
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
Constructors
| ParseError | |
Fields | |
Instances
parseFile :: FilePath -> IO ModuleFromParserSource
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 bSource
eitherToExe returns the Right part of Either or throws the Left part as an dynamic exception.
handleLexError :: (LexError -> IO a) -> IO a -> IO aSource
Handle a dymanic exception of type LexError.
handleParseError :: (ParseError -> IO a) -> IO a -> IO aSource
Handle a dymanic exception of type ParseError.
handleRenameError :: (RenameError -> IO a) -> IO a -> IO aSource
Handle a dymanic exception of type RenameError.
lexInclude :: String -> IO (Either LexError [Token])Source
lex a String and process CSP-M include statements.
filterIgnoredToken :: [Token] -> [Token]Source
Remove comments and unneeded newlines.
type ModuleFromRenaming = Module FromRenamingSource
A module that has gone through renaming
castModule :: Module a -> Module bSource
type Bindings = Map String UniqueIdentSource
Constructors
| TokIdPos TokenId | |
| TokIdSpan TokenId TokenId | |
| TokSpan Token Token | |
| TokPos Token | |
| NoLocation | |
| FixedLoc | |
Fields
| |
renameModule :: ModuleFromParser -> Either RenameError (ModuleFromRenaming, RenameInfo)Source
renameModule renames a Module.
| (also calls mergeFunBinds)
data RenameInfo Source
Gather all information about an renaming.
Constructors
| RenameInfo | |
Fields | |
Instances
getRenaming :: ModuleFromParser -> Either RenameError (Bindings, AstAnnotation UniqueIdent, AstAnnotation UniqueIdent)Source
getRenaming computes two AstAnnotations.
The first one contains all the defining occurences of identifier
The second one contains all the using occurences of identitier.
getRename returns an RenameError if the Module contains unbound
identifiers or illegal redefinitions.
applyRenaming :: (Bindings, AstAnnotation UniqueIdent, AstAnnotation UniqueIdent) -> ModuleFromParser -> ModuleFromRenamingSource
applyRenaming uses SYB to replace turn every Ident in the Module into to the
UIdent version, i.e. set the UniqueIdent.
At the same time, we also replace VarPat x with ConstrPat x if x an toplevel constant
It is an error if the Module contains occurences of Ident that are not covered by
the AstAnnotations.
data RenameError Source
Constructors
| RenameError | |
Fields | |
removeSourceLocations :: Data a => Labeled (Module a) -> Labeled (Module a)Source
removeSourceLocations sets all locationsInfos to NoLocation
removeParens :: Data a => Labeled (Module a) -> Labeled (Module a)Source
removeParens removes all occurences of of Parens,i.e. explicit parentheses from the AST
removeModuleTokens :: Labeled (Module a) -> Labeled (Module a)Source
set the tokenlist in the module datatype to Nothing
unUniqueIdent :: Data a => Labeled (Module a) -> Labeled (Module 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.
showAst :: Data a => Labeled a -> StringSource
'a show function that omits the node labeles. | TODO : fix this is very buggy. | this does not work for Compiles pattern / Arrays
computeFreeNames :: Data a => a -> FreeNamesSource
Compute the FreeNames of an Expression. | This function does only work after renaming has been done. | This implementation is inefficient.
prettyPrintFile :: FilePath -> IO ()Source
run the pretty printer on a file and write the output to | filename.ast and filename.pretty