Safe Haskell | None |
---|---|
Language | Haskell98 |
- fetchAnnsFinal :: RefactGhc Anns
- getTypecheckedModule :: RefactGhc TypecheckedModule
- getRefactStreamModified :: RefactGhc RefacResult
- setRefactStreamModified :: RefacResult -> RefactGhc ()
- getRefactInscopes :: RefactGhc InScopes
- getRefactRenamed :: RefactGhc RenamedSource
- putRefactRenamed :: RenamedSource -> RefactGhc ()
- getRefactParsed :: RefactGhc ParsedSource
- putRefactParsed :: ParsedSource -> Anns -> RefactGhc ()
- setRefactAnns :: Anns -> RefactGhc ()
- putParsedModule :: [Comment] -> TypecheckedModule -> RefactGhc ()
- clearParsedModule :: RefactGhc ()
- getRefactFileName :: RefactGhc (Maybe FilePath)
- getRefactTargetModule :: RefactGhc TargetModule
- getRefactModule :: RefactGhc Module
- getRefactModuleName :: RefactGhc ModuleName
- getRefactNameMap :: RefactGhc NameMap
- liftT :: HasTransform m => forall a. Transform a -> m a
- getRefactDone :: RefactGhc Bool
- setRefactDone :: RefactGhc ()
- clearRefactDone :: RefactGhc ()
- setStateStorage :: StateStorage -> RefactGhc ()
- getStateStorage :: RefactGhc StateStorage
- parseDeclWithAnns :: String -> RefactGhc (LHsDecl RdrName)
- nameSybTransform :: (Monad m, Typeable t) => (Located RdrName -> m (Located RdrName)) -> t -> m t
- nameSybQuery :: (Typeable a, Typeable t) => (Located a -> Maybe r) -> t -> Maybe r
- fileNameFromModSummary :: ModSummary -> FilePath
- mkNewGhcNamePure :: Char -> Int -> Maybe Module -> String -> Name
- logDataWithAnns :: Data a => String -> a -> RefactGhc ()
- logAnns :: String -> RefactGhc ()
- logParsedSource :: String -> RefactGhc ()
- initRefactModule :: [Comment] -> TypecheckedModule -> Maybe RefactModule
- initTokenCacheLayout :: a -> TokenCache a
- initRdrNameMap :: TypecheckedModule -> NameMap
Conveniences for state access
fetchAnnsFinal :: RefactGhc Anns Source
fetch the final annotations
setRefactStreamModified :: RefacResult -> RefactGhc () Source
For testing
putRefactRenamed :: RenamedSource -> RefactGhc () Source
putRefactParsed :: ParsedSource -> Anns -> RefactGhc () Source
Annotations
setRefactAnns :: Anns -> RefactGhc () Source
Internal low level interface to access the current annotations from the RefactGhc state.
putParsedModule :: [Comment] -> TypecheckedModule -> RefactGhc () Source
clearParsedModule :: RefactGhc () Source
New ghc-exactprint interfacing
liftT :: HasTransform m => forall a. Transform a -> m a
State flags for managing generic traversals
setRefactDone :: RefactGhc () Source
clearRefactDone :: RefactGhc () Source
setStateStorage :: StateStorage -> RefactGhc () Source
Parsing source
Utility
nameSybTransform :: (Monad m, Typeable t) => (Located RdrName -> m (Located RdrName)) -> t -> m t Source
logDataWithAnns :: Data a => String -> a -> RefactGhc () Source
logParsedSource :: String -> RefactGhc () Source
For use by the tests only
initRefactModule :: [Comment] -> TypecheckedModule -> Maybe RefactModule Source
initTokenCacheLayout :: a -> TokenCache a Source
initRdrNameMap :: TypecheckedModule -> NameMap Source
We need the ParsedSource because it more closely reflects the actual source code, but must be able to work with the renamed representation of the names involved. This function constructs a map from every Located RdrName in the ParsedSource to its corresponding name in the RenamedSource. It also deals with the wrinkle that we need to Location of the RdrName to make sure we have the right Name, but not all RdrNames have a Location. This function is called before the RefactGhc monad is active.