| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Development.IDE.GHC.Util
Contents
Description
General utility functions, mostly focused around GHC operations.
Synopsis
- modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m ()
 - evalGhcEnv :: HscEnv -> Ghc b -> IO b
 - printRdrName :: RdrName -> String
 - printName :: Name -> String
 - data ParseResult a
 - runParser :: DynFlags -> String -> P a -> ParseResult a
 - lookupPackageConfig :: Unit -> HscEnv -> Maybe UnitInfo
 - textToStringBuffer :: Text -> StringBuffer
 - bytestringToStringBuffer :: ByteString -> StringBuffer
 - stringBufferToByteString :: StringBuffer -> ByteString
 - moduleImportPath :: NormalizedFilePath -> ModuleName -> Maybe FilePath
 - cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule
 - fingerprintToBS :: Fingerprint -> ByteString
 - fingerprintFromByteString :: ByteString -> IO Fingerprint
 - fingerprintFromStringBuffer :: StringBuffer -> IO Fingerprint
 - fingerprintFromPut :: Put -> IO Fingerprint
 - readFileUtf8 :: FilePath -> IO Text
 - hDuplicateTo' :: Handle -> Handle -> IO ()
 - setHieDir :: FilePath -> DynFlags -> DynFlags
 - dontWriteHieFiles :: DynFlags -> DynFlags
 - disableWarningsAsErrors :: DynFlags -> DynFlags
 - traceAst :: (Data a, ExactPrint a, Outputable a, HasCallStack) => String -> a -> a
 - printOutputable :: Outputable a => a -> Text
 
Documentation
modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m () Source #
Used to modify dyn flags in preference to calling setSessionDynFlags,
   since that function also reloads packages (which is very slow).
GHC wrappers
data ParseResult a #
The result of running a parser.
Constructors
| POk | The parser has consumed a (possibly empty) prefix
   of the input and produced a result. Use   | 
Fields 
  | |
| PFailed | The parser has consumed a (possibly empty) prefix of the input and failed.  | 
Fields 
  | |
lookupPackageConfig :: Unit -> HscEnv -> Maybe UnitInfo Source #
Given a Unit try and find the associated PackageConfig in the environment.
textToStringBuffer :: Text -> StringBuffer Source #
Convert from the text package to the GHC StringBuffer.
   Currently implemented somewhat inefficiently (if it ever comes up in a profile).
moduleImportPath :: NormalizedFilePath -> ModuleName -> Maybe FilePath Source #
Given a module location, and its parse tree, figure out what is the include directory implied by it.
   For example, given the file /usr/Test/Foo/Bar.hs with the module name Foo.Bar the directory
   /usr/Test should be on the include path to find sibling modules.
cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule Source #
Convert from a CgGuts to a CoreModule.
fingerprintToBS :: Fingerprint -> ByteString Source #
Convert a Fingerprint to a ByteString by copying the byte across.
   Will produce an 8 byte unreadable ByteString.
fingerprintFromStringBuffer :: StringBuffer -> IO Fingerprint Source #
Take the Fingerprint of a StringBuffer.
fingerprintFromPut :: Put -> IO Fingerprint Source #
General utilities
readFileUtf8 :: FilePath -> IO Text Source #
Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.
hDuplicateTo' :: Handle -> Handle -> IO () Source #
A slightly modified version of hDuplicateTo from GHC.
   Importantly, it avoids the bug listed in https://gitlab.haskell.org/ghc/ghc/merge_requests/2318.
dontWriteHieFiles :: DynFlags -> DynFlags Source #
traceAst :: (Data a, ExactPrint a, Outputable a, HasCallStack) => String -> a -> a Source #
Prints an Outputable value to stderr and to an HTML file for further inspection
printOutputable :: Outputable a => a -> Text Source #
Print a GHC value in defaultUserStyle without unique symbols.
This is the most common print utility, will print with a user-friendly style like: a_a4ME as a.
It internal using showSDocUnsafe with unsafeGlobalDynFlags.