Safe Haskell | None |
---|---|
Language | Haskell2010 |
Attempt at hiding the GHC version differences we can.
Synopsis
- newtype NameCacheUpdater = NCU {
- updateNameCache :: forall c. (NameCache -> (NameCache, c)) -> IO c
- hPutStringBuffer :: Handle -> StringBuffer -> IO ()
- addIncludePathsQuote :: FilePath -> DynFlags -> DynFlags
- getModuleHash :: ModIface -> Fingerprint
- setUpTypedHoles :: DynFlags -> DynFlags
- upNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
- disableWarningsAsErrors :: DynFlags -> DynFlags
- reLoc :: Located a -> Located a
- reLocA :: Located a -> Located a
- getMessages' :: PState -> DynFlags -> (Bag WarnMsg, Bag ErrMsg)
- pattern PFailedWithErrorMessages :: (DynFlags -> ErrorMessages) -> ParseResult a
- type RefMap a = Map Identifier [(Span, IdentifierDetails a)]
- nodeInfo' :: Ord a => HieAST a -> NodeInfo a
- getNodeIds :: HieAST a -> NodeIdentifiers a
- nodeInfoFromSource :: HieAST a -> Maybe (NodeInfo a)
- isAnnotationInNodeInfo :: (FastString, FastString) -> NodeInfo a -> Bool
- mkAstNode :: NodeInfo a -> Span -> [HieAST a] -> HieAST a
- combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan
- isQualifiedImport :: ImportDecl a -> Bool
- data GhcVersion
- ghcVersion :: GhcVersion
- ghcVersionStr :: String
- data HieFileResult = HieFileResult {}
- data HieFile = HieFile {}
- hieExportNames :: HieFile -> [(SrcSpan, Name)]
- mkHieFile' :: ModSummary -> [AvailInfo] -> HieASTs Type -> ByteString -> Hsc HieFile
- enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
- writeHieFile :: FilePath -> HieFile -> IO ()
- readHieFile :: NameCacheUpdater -> FilePath -> IO HieFileResult
- supportsHieFiles :: Bool
- setHieDir :: FilePath -> DynFlags -> DynFlags
- dontWriteHieFiles :: DynFlags -> DynFlags
- module Compat.HieTypes
- module Compat.HieUtils
- module Development.IDE.GHC.Compat.Core
- module Development.IDE.GHC.Compat.Env
- module Development.IDE.GHC.Compat.ExactPrint
- module Development.IDE.GHC.Compat.Iface
- module Development.IDE.GHC.Compat.Logger
- module Development.IDE.GHC.Compat.Outputable
- module Development.IDE.GHC.Compat.Parser
- module Development.IDE.GHC.Compat.Plugins
- module Development.IDE.GHC.Compat.Units
- data Option
- runUnlit :: Logger -> DynFlags -> [Option] -> IO ()
- runPp :: Logger -> DynFlags -> [Option] -> IO ()
Documentation
newtype NameCacheUpdater #
A function that atomically updates the name cache given a modifier function. The second result of the modifier function will be the result of the IO action.
NCU | |
|
hPutStringBuffer :: Handle -> StringBuffer -> IO () #
getModuleHash :: ModIface -> Fingerprint Source #
setUpTypedHoles :: DynFlags -> DynFlags Source #
pattern PFailedWithErrorMessages :: (DynFlags -> ErrorMessages) -> ParseResult a Source #
type RefMap a = Map Identifier [(Span, IdentifierDetails a)] Source #
getNodeIds :: HieAST a -> NodeIdentifiers a Source #
isAnnotationInNodeInfo :: (FastString, FastString) -> NodeInfo a -> Bool Source #
isQualifiedImport :: ImportDecl a -> Bool Source #
data GhcVersion Source #
Instances
Eq GhcVersion Source # | |
Defined in Development.IDE.GHC.Compat (==) :: GhcVersion -> GhcVersion -> Bool # (/=) :: GhcVersion -> GhcVersion -> Bool # | |
Ord GhcVersion Source # | |
Defined in Development.IDE.GHC.Compat compare :: GhcVersion -> GhcVersion -> Ordering # (<) :: GhcVersion -> GhcVersion -> Bool # (<=) :: GhcVersion -> GhcVersion -> Bool # (>) :: GhcVersion -> GhcVersion -> Bool # (>=) :: GhcVersion -> GhcVersion -> Bool # max :: GhcVersion -> GhcVersion -> GhcVersion # min :: GhcVersion -> GhcVersion -> GhcVersion # | |
Show GhcVersion Source # | |
Defined in Development.IDE.GHC.Compat showsPrec :: Int -> GhcVersion -> ShowS # show :: GhcVersion -> String # showList :: [GhcVersion] -> ShowS # |
HIE Compat
data HieFileResult #
GHC builds up a wealth of information about Haskell source as it compiles it.
.hie
files are a way of persisting some of this information to disk so that
external tools that need to work with haskell source don't need to parse,
typecheck, and rename all over again. These files contain:
a simplified AST
- nodes are annotated with source positions and types
- identifiers are annotated with scope information
- the raw bytes of the initial Haskell source
Besides saving compilation cycles, .hie
files also offer a more stable
interface than the GHC API.
HieFile | |
|
mkHieFile' :: ModSummary -> [AvailInfo] -> HieASTs Type -> ByteString -> Hsc HieFile Source #
writeHieFile :: FilePath -> HieFile -> IO () #
Write a HieFile
to the given FilePath
, with a proper header and
symbol tables for Name
s and FastString
s
readHieFile :: NameCacheUpdater -> FilePath -> IO HieFileResult #
dontWriteHieFiles :: DynFlags -> DynFlags Source #
module Compat.HieTypes
module Compat.HieUtils
Compat modules
Extras that rely on compat modules
SysTools
When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.