module Development.IDE.GHC.Util(
HscEnvEq,
hscEnv, newHscEnvEq,
modifyDynFlags,
evalGhcEnv,
runGhcEnv,
deps,
prettyPrint,
printRdrName,
printName,
ParseResult(..), runParser,
lookupPackageConfig,
textToStringBuffer,
bytestringToStringBuffer,
stringBufferToByteString,
moduleImportPath,
cgGutsToCoreModule,
fingerprintToBS,
fingerprintFromStringBuffer,
readFileUtf8,
hDuplicateTo',
setHieDir,
dontWriteHieFiles,
) where
import Control.Concurrent
import Data.List.Extra
import Data.ByteString.Internal (ByteString(..))
import Data.Maybe
import Data.Typeable
import qualified Data.ByteString.Internal as BS
import Fingerprint
import GhcMonad
import Control.Exception
import Data.IORef
import FileCleanup
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Storable
import GHC.IO.BufferedIO (BufferedIO)
import GHC.IO.Device as IODevice
import GHC.IO.Encoding
import GHC.IO.Exception
import GHC.IO.Handle.Types
import GHC.IO.Handle.Internals
import Data.Unique
import Development.Shake.Classes
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Encoding.Error as T
import qualified Data.ByteString as BS
import Lexer
import StringBuffer
import System.FilePath
import HscTypes (cg_binds, md_types, cg_module, ModDetails, CgGuts, ic_dflags, hsc_IC, HscEnv(hsc_dflags))
import PackageConfig (PackageConfig)
import Outputable (showSDocUnsafe, ppr, showSDoc, Outputable)
import Packages (getPackageConfigMap, lookupPackage')
import SrcLoc (mkRealSrcLoc)
import FastString (mkFastString)
import DynFlags (emptyFilesToClean, unsafeGlobalDynFlags)
import Module (moduleNameSlashes, InstalledUnitId)
import OccName (parenSymOcc)
import RdrName (nameRdrName, rdrNameOcc)
import Development.IDE.GHC.Compat as GHC
import Development.IDE.Types.Location
modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m ()
modifyDynFlags f = do
newFlags <- f <$> getSessionDynFlags
modifySession $ \h ->
h { hsc_dflags = newFlags, hsc_IC = (hsc_IC h) {ic_dflags = newFlags} }
lookupPackageConfig :: UnitId -> HscEnv -> Maybe PackageConfig
lookupPackageConfig unitId env =
lookupPackage' False pkgConfigMap unitId
where
pkgConfigMap =
getPackageConfigMap $ hsc_dflags env
textToStringBuffer :: T.Text -> StringBuffer
textToStringBuffer = stringToStringBuffer . T.unpack
runParser :: DynFlags -> String -> P a -> ParseResult a
runParser flags str parser = unP parser parseState
where
filename = "<interactive>"
location = mkRealSrcLoc (mkFastString filename) 1 1
buffer = stringToStringBuffer str
parseState = mkPState flags buffer location
stringBufferToByteString :: StringBuffer -> ByteString
stringBufferToByteString StringBuffer{..} = PS buf cur len
bytestringToStringBuffer :: ByteString -> StringBuffer
bytestringToStringBuffer (PS buf cur len) = StringBuffer{..}
prettyPrint :: Outputable a => a -> String
prettyPrint = showSDoc unsafeGlobalDynFlags . ppr
printRdrName :: RdrName -> String
printRdrName name = showSDocUnsafe $ parenSymOcc rn (ppr rn)
where
rn = rdrNameOcc name
printName :: Name -> String
printName = printRdrName . nameRdrName
evalGhcEnv :: HscEnv -> Ghc b -> IO b
evalGhcEnv env act = snd <$> runGhcEnv env act
runGhcEnv :: HscEnv -> Ghc a -> IO (HscEnv, a)
runGhcEnv env act = do
filesToClean <- newIORef emptyFilesToClean
dirsToClean <- newIORef mempty
let dflags = (hsc_dflags env){filesToClean=filesToClean, dirsToClean=dirsToClean, useUnicode=True}
ref <- newIORef env{hsc_dflags=dflags}
res <- unGhc act (Session ref) `finally` do
cleanTempFiles dflags
cleanTempDirs dflags
(,res) <$> readIORef ref
moduleImportPath :: NormalizedFilePath -> GHC.ModuleName -> Maybe FilePath
moduleImportPath (takeDirectory . fromNormalizedFilePath -> pathDir) mn
| modDir == "." = Just pathDir
| otherwise = dropTrailingPathSeparator <$> stripSuffix modDir pathDir
where
modDir =
takeDirectory $
fromNormalizedFilePath $ toNormalizedFilePath' $
moduleNameSlashes mn
data HscEnvEq
= HscEnvEq !Unique !HscEnv
[(InstalledUnitId, DynFlags)]
hscEnv :: HscEnvEq -> HscEnv
hscEnv = either error id . hscEnv'
hscEnv' :: HscEnvEq -> Either String HscEnv
hscEnv' (HscEnvEq _ x _) = Right x
deps :: HscEnvEq -> [(InstalledUnitId, DynFlags)]
deps (HscEnvEq _ _ u) = u
newHscEnvEq :: HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
newHscEnvEq e uids = do u <- newUnique; return $ HscEnvEq u e uids
instance Show HscEnvEq where
show (HscEnvEq a _ _) = "HscEnvEq " ++ show (hashUnique a)
instance Eq HscEnvEq where
HscEnvEq a _ _ == HscEnvEq b _ _ = a == b
instance NFData HscEnvEq where
rnf (HscEnvEq a b c) = rnf (hashUnique a) `seq` b `seq` c `seq` ()
instance Hashable HscEnvEq where
hashWithSalt s (HscEnvEq a _b _c) = hashWithSalt s a
instance Binary HscEnvEq where
put _ = error "not really"
get = error "not really"
readFileUtf8 :: FilePath -> IO T.Text
readFileUtf8 f = T.decodeUtf8With T.lenientDecode <$> BS.readFile f
cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule
cgGutsToCoreModule safeMode guts modDetails = CoreModule
(cg_module guts)
(md_types modDetails)
(cg_binds guts)
safeMode
fingerprintToBS :: Fingerprint -> BS.ByteString
fingerprintToBS (Fingerprint a b) = BS.unsafeCreate 8 $ \ptr -> do
ptr <- pure $ castPtr ptr
pokeElemOff ptr 0 a
pokeElemOff ptr 1 b
fingerprintFromStringBuffer :: StringBuffer -> IO Fingerprint
fingerprintFromStringBuffer (StringBuffer buf len cur) =
withForeignPtr buf $ \ptr -> fingerprintData (ptr `plusPtr` cur) len
hDuplicateTo' :: Handle -> Handle -> IO ()
hDuplicateTo' h1@(FileHandle path m1) h2@(FileHandle _ m2) = do
withHandle__' "hDuplicateTo" h2 m2 $ \h2_ -> do
_ <- flushWriteBuffer h2_ `catch` \(_ :: IOException) -> pure ()
withHandle_' "hDuplicateTo" h1 m1 $ \h1_ -> do
dupHandleTo path h1 Nothing h2_ h1_ (Just handleFinalizer)
hDuplicateTo' h1@(DuplexHandle path r1 w1) h2@(DuplexHandle _ r2 w2) = do
withHandle__' "hDuplicateTo" h2 w2 $ \w2_ -> do
_ <- hClose_help w2_
withHandle_' "hDuplicateTo" h1 w1 $ \w1_ -> do
dupHandleTo path h1 Nothing w2_ w1_ (Just handleFinalizer)
withHandle__' "hDuplicateTo" h2 r2 $ \r2_ -> do
_ <- hClose_help r2_
withHandle_' "hDuplicateTo" h1 r1 $ \r1_ -> do
dupHandleTo path h1 (Just w1) r2_ r1_ Nothing
hDuplicateTo' h1 _ =
ioe_dupHandlesNotCompatible h1
dupHandleTo :: FilePath
-> Handle
-> Maybe (MVar Handle__)
-> Handle__
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle__
dupHandleTo filepath h other_side
_hto_@Handle__{haDevice=devTo}
h_@Handle__{haDevice=dev} mb_finalizer = do
flushBuffer h_
case cast devTo of
Nothing -> ioe_dupHandlesNotCompatible h
Just dev' -> do
_ <- IODevice.dup2 dev dev'
FileHandle _ m <- dupHandle_ dev' filepath other_side h_ mb_finalizer
takeMVar m
dupHandle_ :: (IODevice dev, BufferedIO dev, Typeable dev) => dev
-> FilePath
-> Maybe (MVar Handle__)
-> Handle__
-> Maybe HandleFinalizer
-> IO Handle
dupHandle_ new_dev filepath other_side _h_@Handle__{..} mb_finalizer = do
mb_codec <- if isJust haEncoder then fmap Just getLocaleEncoding else return Nothing
mkHandle new_dev filepath haType True mb_codec
NewlineMode { inputNL = haInputNL, outputNL = haOutputNL }
mb_finalizer other_side
ioe_dupHandlesNotCompatible :: Handle -> IO a
ioe_dupHandlesNotCompatible h =
ioException (IOError (Just h) IllegalOperation "hDuplicateTo"
"handles are incompatible" Nothing Nothing)