Skip to content

Commit 19a346a

Browse files
ndmitchellcocreature
authored andcommitted
Add documentation (#368)
* Add documentation for Util.hs * Add documentation to OfInterest
1 parent 7e133ea commit 19a346a

File tree

2 files changed

+46
-32
lines changed

2 files changed

+46
-32
lines changed

src/Development/IDE/Core/OfInterest.hs

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,53 +1,49 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4-
5-
{-# LANGUAGE TypeFamilies #-}
4+
{-# LANGUAGE TypeFamilies #-}
65
{-# LANGUAGE FlexibleInstances #-}
76

8-
-- | A Shake implementation of the compiler service, built
9-
-- using the "Shaker" abstraction layer for in-memory use.
10-
--
7+
-- | Utilities and state for the files of interest - those which are currently
8+
-- open in the editor. The useful function is 'getFilesOfInterest'.
119
module Development.IDE.Core.OfInterest(
1210
ofInterestRules,
1311
getFilesOfInterest, setFilesOfInterest, modifyFilesOfInterest,
1412
) where
1513

16-
import Control.Concurrent.Extra
14+
import Control.Concurrent.Extra
1715
import Data.Binary
1816
import Data.Hashable
1917
import Control.DeepSeq
2018
import GHC.Generics
2119
import Data.Typeable
2220
import qualified Data.ByteString.UTF8 as BS
2321
import Control.Exception
24-
import Development.IDE.Types.Location
25-
import Development.IDE.Types.Logger
26-
import Data.Set (Set)
27-
import qualified Data.Set as Set
22+
import Data.Set (Set)
23+
import qualified Data.Set as Set
2824
import qualified Data.Text as T
2925
import Data.Tuple.Extra
3026
import Data.Functor
31-
import Development.Shake
32-
33-
import Development.IDE.Core.Shake
27+
import Development.Shake
3428

29+
import Development.IDE.Types.Location
30+
import Development.IDE.Types.Logger
31+
import Development.IDE.Core.Shake
3532

3633

3734
newtype OfInterestVar = OfInterestVar (Var (Set NormalizedFilePath))
3835
instance IsIdeGlobal OfInterestVar
3936

40-
4137
type instance RuleResult GetFilesOfInterest = Set NormalizedFilePath
4238

43-
4439
data GetFilesOfInterest = GetFilesOfInterest
4540
deriving (Eq, Show, Typeable, Generic)
4641
instance Hashable GetFilesOfInterest
4742
instance NFData GetFilesOfInterest
4843
instance Binary GetFilesOfInterest
4944

5045

46+
-- | The rule that initialises the files of interest state.
5147
ofInterestRules :: Rules ()
5248
ofInterestRules = do
5349
addIdeGlobal . OfInterestVar =<< liftIO (newVar Set.empty)
@@ -57,6 +53,7 @@ ofInterestRules = do
5753
pure (Just $ BS.fromString $ show filesOfInterest, ([], Just filesOfInterest))
5854

5955

56+
-- | Get the files that are open in the IDE.
6057
getFilesOfInterest :: Action (Set NormalizedFilePath)
6158
getFilesOfInterest = useNoFile_ GetFilesOfInterest
6259

@@ -65,7 +62,8 @@ getFilesOfInterest = useNoFile_ GetFilesOfInterest
6562
------------------------------------------------------------
6663
-- Exposed API
6764

68-
-- | Set the files-of-interest which will be built and kept-up-to-date.
65+
-- | Set the files-of-interest - not usually necessary or advisable.
66+
-- The LSP client will keep this information up to date.
6967
setFilesOfInterest :: IdeState -> Set NormalizedFilePath -> IO ()
7068
setFilesOfInterest state files = modifyFilesOfInterest state (const files)
7169

@@ -74,6 +72,8 @@ getFilesOfInterestUntracked = do
7472
OfInterestVar var <- getIdeGlobalAction
7573
liftIO $ readVar var
7674

75+
-- | Modify the files-of-interest - not usually necessary or advisable.
76+
-- The LSP client will keep this information up to date.
7777
modifyFilesOfInterest :: IdeState -> (Set NormalizedFilePath -> Set NormalizedFilePath) -> IO ()
7878
modifyFilesOfInterest state f = do
7979
OfInterestVar var <- getIdeGlobalState state

src/Development/IDE/GHC/Util.hs

Lines changed: 30 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -5,23 +5,22 @@
55
{-# LANGUAGE CPP #-}
66
#include "ghc-api-version.h"
77

8-
-- | GHC utility functions. Importantly, code using our GHC should never:
9-
--
10-
-- * Call runGhc, use runGhcFast instead. It's faster and doesn't require config we don't have.
11-
--
12-
-- * Call setSessionDynFlags, use modifyDynFlags instead. It's faster and avoids loading packages.
8+
-- | General utility functions, mostly focused around GHC operations.
139
module Development.IDE.GHC.Util(
14-
lookupPackageConfig,
10+
-- * HcsEnv and environment
11+
HscEnvEq, hscEnv, newHscEnvEq,
1512
modifyDynFlags,
1613
fakeDynFlags,
17-
prettyPrint,
1814
runGhcEnv,
19-
textToStringBuffer,
15+
-- * GHC wrappers
16+
prettyPrint,
17+
lookupPackageConfig,
2018
moduleImportPath,
21-
HscEnvEq, hscEnv, newHscEnvEq,
19+
cgGutsToCoreModule,
20+
-- * General utilities
21+
textToStringBuffer,
2222
readFileUtf8,
2323
hDuplicateTo',
24-
cgGutsToCoreModule
2524
) where
2625

2726
import Config
@@ -60,6 +59,8 @@ import Development.IDE.Types.Location
6059
----------------------------------------------------------------------
6160
-- GHC setup
6261

62+
-- | Used to modify dyn flags in preference to calling 'setSessionDynFlags',
63+
-- since that function also reloads packages (which is very slow).
6364
modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags) -> m ()
6465
modifyDynFlags f = do
6566
newFlags <- f <$> getSessionDynFlags
@@ -68,6 +69,7 @@ modifyDynFlags f = do
6869
modifySession $ \h ->
6970
h { hsc_dflags = newFlags, hsc_IC = (hsc_IC h) {ic_dflags = newFlags} }
7071

72+
-- | Given a 'UnitId' try and find the associated 'PackageConfig' in the environment.
7173
lookupPackageConfig :: UnitId -> HscEnv -> Maybe PackageConfig
7274
lookupPackageConfig unitId env =
7375
lookupPackage' False pkgConfigMap unitId
@@ -78,14 +80,18 @@ lookupPackageConfig unitId env =
7880
getPackageConfigMap $ hsc_dflags env
7981

8082

81-
-- would be nice to do this more efficiently...
83+
-- | Convert from the @text@ package to the @GHC@ 'StringBuffer'.
84+
-- Currently implemented somewhat inefficiently (if it ever comes up in a profile).
8285
textToStringBuffer :: T.Text -> StringBuffer
8386
textToStringBuffer = stringToStringBuffer . T.unpack
8487

8588

89+
-- | Pretty print a GHC value using 'fakeDynFlags'.
8690
prettyPrint :: Outputable a => a -> String
8791
prettyPrint = showSDoc fakeDynFlags . ppr
8892

93+
-- | Run a 'Ghc' monad value using an existing 'HscEnv'. Sets up and tears down all the required
94+
-- pieces, but designed to be more efficient than a standard 'runGhc'.
8995
runGhcEnv :: HscEnv -> Ghc a -> IO a
9096
runGhcEnv env act = do
9197
filesToClean <- newIORef emptyFilesToClean
@@ -96,8 +102,8 @@ runGhcEnv env act = do
96102
cleanTempFiles dflags
97103
cleanTempDirs dflags
98104

99-
-- Fake DynFlags which are mostly undefined, but define enough to do a
100-
-- little bit.
105+
-- | A 'DynFlags' value where most things are undefined. It's sufficient to call pretty printing,
106+
-- but not much else.
101107
fakeDynFlags :: DynFlags
102108
fakeDynFlags = defaultDynFlags settings mempty
103109
where
@@ -120,6 +126,9 @@ fakeDynFlags = defaultDynFlags settings mempty
120126
, pc_WORD_SIZE=8
121127
}
122128

129+
-- | Given a module location, and its parse tree, figure out what is the include directory implied by it.
130+
-- For example, given the file @\/usr\/\Test\/Foo\/Bar.hs@ with the module name @Foo.Bar@ the directory
131+
-- @\/usr\/Test@ should be on the include path to find sibling modules.
123132
moduleImportPath :: NormalizedFilePath -> GHC.ParsedModule -> Maybe FilePath
124133
-- The call to takeDirectory is required since DAML does not require that
125134
-- the file name matches the module name in the last component.
@@ -137,12 +146,15 @@ moduleImportPath (takeDirectory . fromNormalizedFilePath -> pathDir) pm
137146
fromNormalizedFilePath $ toNormalizedFilePath $
138147
moduleNameSlashes $ GHC.moduleName mod'
139148

140-
-- | An HscEnv with equality.
149+
-- | An 'HscEnv' with equality. Two values are considered equal
150+
-- if they are created with the same call to 'newHscEnvEq'.
141151
data HscEnvEq = HscEnvEq Unique HscEnv
142152

153+
-- | Unwrap an 'HsEnvEq'.
143154
hscEnv :: HscEnvEq -> HscEnv
144155
hscEnv (HscEnvEq _ x) = x
145156

157+
-- | Wrap an 'HscEnv' into an 'HscEnvEq'.
146158
newHscEnvEq :: HscEnv -> IO HscEnvEq
147159
newHscEnvEq e = do u <- newUnique; return $ HscEnvEq u e
148160

@@ -155,18 +167,20 @@ instance Eq HscEnvEq where
155167
instance NFData HscEnvEq where
156168
rnf (HscEnvEq a b) = rnf (hashUnique a) `seq` b `seq` ()
157169

170+
-- | Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.
158171
readFileUtf8 :: FilePath -> IO T.Text
159172
readFileUtf8 f = T.decodeUtf8With T.lenientDecode <$> BS.readFile f
160173

174+
-- | Convert from a 'CgGuts' to a 'CoreModule'.
161175
cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule
162176
cgGutsToCoreModule safeMode guts modDetails = CoreModule
163177
(cg_module guts)
164178
(md_types modDetails)
165179
(cg_binds guts)
166180
safeMode
167181

168-
-- This is a slightly modified version of hDuplicateTo in GHC.
169-
-- See the inline comment for more details.
182+
-- | A slightly modified version of 'hDuplicateTo' from GHC.
183+
-- Importantly, it avoids the bug listed in https://gitlab.haskell.org/ghc/ghc/merge_requests/2318.
170184
hDuplicateTo' :: Handle -> Handle -> IO ()
171185
hDuplicateTo' h1@(FileHandle path m1) h2@(FileHandle _ m2) = do
172186
withHandle__' "hDuplicateTo" h2 m2 $ \h2_ -> do

0 commit comments

Comments
 (0)