CSPM-Frontend-0.6.8.0: A CSP-M parser compatible with FDR-2.91

PortabilityGHC-only
Stabilityexperimental
MaintainerFontaine@cs.uni-duesseldorf.de

Language.CSPM.Frontend

Description

Frontend contains some reexports from other modules

Synopsis

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

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.

lexPlain :: String -> Either LexError [Token]Source

lex a String .

filterIgnoredToken :: [Token] -> [Token]Source

Remove comments and unneeded newlines.

data Module a Source

Instances

Typeable1 Module 
Eq (Module a) 
Data a => Data (Module a) 
Ord (Module a) 
Show (Module a) 
PP (Module a) 

type ModuleFromRenaming = Module FromRenamingSource

A module that has gone through renaming

data Labeled t Source

Constructors

Labeled 

Fields

nodeId :: NodeId
 
srcLoc :: SrcLoc
 
unLabel :: t
 

Instances

Typeable1 Labeled 
Eq t => Eq (Labeled t) 
Data t => Data (Labeled t) 
Ord t => Ord (Labeled t) 
Show t => Show (Labeled t) 
PP x => PP (Labeled x) 

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.

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.

setNodeIdsZero :: Data a => Labeled (Module a) -> Labeled (Module a)Source

Set all NodeIds to zero.

pp :: PP x => x -> DocSource

prettyPrintFile :: FilePath -> IO ()Source

run the pretty printer on a file and write the output to | filename.ast and filename.pretty