diff options
| author | Ben Gamari <ben@smart-cactus.org> | 2021-01-05 15:54:42 -0500 | 
|---|---|---|
| committer | Ben Gamari <ben@smart-cactus.org> | 2021-01-05 16:14:31 -0500 | 
| commit | 1e56f63c3197e7ca1c1e506e083c2bad25d08793 (patch) | |
| tree | 7152e5a53fe1c18e6fd5044d5aa3168ab99c3cc6 /haddock-api/src/Haddock/Utils.hs | |
| parent | 1d657cf377b5f147b08aafb3ab3a5d11be538331 (diff) | |
| parent | 665226f384ee9b0a66a98638ede9eff845f6c45b (diff) | |
Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0
Diffstat (limited to 'haddock-api/src/Haddock/Utils.hs')
| -rw-r--r-- | haddock-api/src/Haddock/Utils.hs | 184 | 
1 files changed, 27 insertions, 157 deletions
| diff --git a/haddock-api/src/Haddock/Utils.hs b/haddock-api/src/Haddock/Utils.hs index 8346a477..0c9c6073 100644 --- a/haddock-api/src/Haddock/Utils.hs +++ b/haddock-api/src/Haddock/Utils.hs @@ -13,15 +13,9 @@  -----------------------------------------------------------------------------  module Haddock.Utils ( -  -- * Misc utilities -  restrictTo, emptyHsQTvs, -  toDescription, toInstalledDescription, -  mkEmptySigWcType, addClassContext, lHsQTyVarsToTypes, -    -- * Filename utilities    moduleHtmlFile, moduleHtmlFile',    contentsHtmlFile, indexHtmlFile, indexJsonFile, -  moduleIndexFrameName, mainFrameName, synopsisFrameName,    subIndexHtmlFile,    haddockJsFile, jsQuickJumpFile,    quickJumpCssFile, @@ -32,7 +26,7 @@ module Haddock.Utils (    makeAnchorId,    -- * Miscellaneous utilities -  getProgramName, bye, die, dieMsg, noDieMsg, mapSnd, mapMaybeM, escapeStr, +  getProgramName, bye, die, escapeStr,    writeUtf8File, withTempDir,    -- * HTML cross reference mapping @@ -45,11 +39,8 @@ module Haddock.Utils (    replace,    spanWith, -  -- * MTL stuff -  MonadIO(..), -    -- * Logging -  parseVerbosity, +  parseVerbosity, Verbosity(..), silent, normal, verbose, deafening,    out,    -- * System tools @@ -59,48 +50,54 @@ module Haddock.Utils (  import Documentation.Haddock.Doc (emptyMetaDoc)  import Haddock.Types -import Haddock.GhcUtils -import GHC.Types.Basic ( PromotionFlag(..) ) -import GHC.Utils.Exception (ExceptionMonad)  import GHC  import GHC.Types.Name -import Control.Monad ( liftM ) -import Control.Monad.Catch ( bracket_ ) +import Control.Monad.IO.Class ( MonadIO(..) ) +import Control.Monad.Catch ( MonadMask, bracket_ )  import Data.Char ( isAlpha, isAlphaNum, isAscii, ord, chr )  import Numeric ( showIntAtBase )  import Data.Map ( Map )  import qualified Data.Map as Map hiding ( Map )  import Data.IORef ( IORef, newIORef, readIORef )  import Data.List ( isSuffixOf ) -import Data.Maybe ( mapMaybe )  import System.Environment ( getProgName )  import System.Exit  import System.Directory ( createDirectory, removeDirectoryRecursive ) -import System.IO ( hPutStr, hSetEncoding, IOMode(..), stderr, utf8, withFile ) +import System.IO ( hPutStr, hSetEncoding, IOMode(..), utf8, withFile )  import System.IO.Unsafe ( unsafePerformIO )  import qualified System.FilePath.Posix as HtmlPath -import Distribution.Verbosity -import Distribution.ReadE  #ifndef mingw32_HOST_OS  import qualified System.Posix.Internals  #endif -import GHC.Utils.Monad ( MonadIO(..) ) - -import GHC.Core.Multiplicity - -  --------------------------------------------------------------------------------  -- * Logging  -------------------------------------------------------------------------------- +data Verbosity = Silent | Normal | Verbose | Deafening +  deriving (Eq, Ord, Enum, Bounded, Show) -parseVerbosity :: String -> Either String Verbosity -parseVerbosity = runReadE flagToVerbosity +silent, normal, verbose, deafening :: Verbosity +silent    = Silent +normal    = Normal +verbose   = Verbose +deafening = Deafening +-- | Parse out a verbosity level. Inspired from Cabal's verbosity parsing. +parseVerbosity :: String -> Either String Verbosity +parseVerbosity "0" = Right Silent +parseVerbosity "1" = Right Normal +parseVerbosity "2" = Right Silent +parseVerbosity "3" = Right Deafening +parseVerbosity "silent"    = return Silent +parseVerbosity "normal"    = return Normal +parseVerbosity "verbose"   = return Verbose +parseVerbosity "debug"     = return Deafening +parseVerbosity "deafening" = return Deafening +parseVerbosity other = Left ("Can't parse verbosity " ++ other)  -- | Print a message to stdout, if it is not too verbose  out :: MonadIO m @@ -117,115 +114,14 @@ out progVerbosity msgVerbosity msg  -------------------------------------------------------------------------------- --- | Extract a module's short description. -toDescription :: Interface -> Maybe (MDoc Name) -toDescription = fmap mkMeta . hmi_description . ifaceInfo - - --- | Extract a module's short description. -toInstalledDescription :: InstalledInterface -> Maybe (MDoc Name) -toInstalledDescription = fmap mkMeta . hmi_description . instInfo  mkMeta :: Doc a -> MDoc a  mkMeta x = emptyMetaDoc { _doc = x } -mkEmptySigWcType :: LHsType GhcRn -> LHsSigWcType GhcRn --- Dubious, because the implicit binders are empty even --- though the type might have free varaiables -mkEmptySigWcType ty = mkEmptyWildCardBndrs (mkEmptyImplicitBndrs ty) - -addClassContext :: Name -> LHsQTyVars GhcRn -> LSig GhcRn -> LSig GhcRn --- Add the class context to a class-op signature -addClassContext cls tvs0 (L pos (ClassOpSig _ _ lname ltype)) -  = L pos (TypeSig noExtField lname (mkEmptySigWcType (go (hsSigType ltype)))) -          -- The mkEmptySigWcType is suspicious -  where -    go (L loc (HsForAllTy { hst_tele = tele, hst_body = ty })) -       = L loc (HsForAllTy { hst_xforall = noExtField -                           , hst_tele = tele, hst_body = go ty }) -    go (L loc (HsQualTy { hst_ctxt = ctxt, hst_body = ty })) -       = L loc (HsQualTy { hst_xqual = noExtField -                         , hst_ctxt = add_ctxt ctxt, hst_body = ty }) -    go (L loc ty) -       = L loc (HsQualTy { hst_xqual = noExtField -                         , hst_ctxt = add_ctxt (L loc []), hst_body = L loc ty }) - -    extra_pred = nlHsTyConApp Prefix cls (lHsQTyVarsToTypes tvs0) -    add_ctxt (L loc preds) = L loc (extra_pred : preds) - -addClassContext _ _ sig = sig   -- E.g. a MinimalSig is fine - -lHsQTyVarsToTypes :: LHsQTyVars GhcRn -> [LHsTypeArg GhcRn] -lHsQTyVarsToTypes tvs -  = [ HsValArg $ noLoc (HsTyVar noExtField NotPromoted (noLoc (hsLTyVarName tv))) -    | tv <- hsQTvExplicit tvs ] - --------------------------------------------------------------------------------- --- * Making abstract declarations --------------------------------------------------------------------------------- - - -restrictTo :: [Name] -> LHsDecl GhcRn -> LHsDecl GhcRn -restrictTo names (L loc decl) = L loc $ case decl of -  TyClD x d | isDataDecl d  -> -    TyClD x (d { tcdDataDefn = restrictDataDefn names (tcdDataDefn d) }) -  TyClD x d | isClassDecl d -> -    TyClD x (d { tcdSigs = restrictDecls names (tcdSigs d), -               tcdATs = restrictATs names (tcdATs d) }) -  _ -> decl - -restrictDataDefn :: [Name] -> HsDataDefn GhcRn -> HsDataDefn GhcRn -restrictDataDefn names defn@(HsDataDefn { dd_ND = new_or_data, dd_cons = cons }) -  | DataType <- new_or_data -  = defn { dd_cons = restrictCons names cons } -  | otherwise    -- Newtype -  = case restrictCons names cons of -      []    -> defn { dd_ND = DataType, dd_cons = [] } -      [con] -> defn { dd_cons = [con] } -      _ -> error "Should not happen" - -restrictCons :: [Name] -> [LConDecl GhcRn] -> [LConDecl GhcRn] -restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ] -  where -    keep d | any (\n -> n `elem` names) (map unLoc $ getConNames d) = -      case con_args d of -        PrefixCon _ -> Just d -        RecCon fields -          | all field_avail (unL fields) -> Just d -          | otherwise -> Just (d { con_args = PrefixCon (field_types (map unL (unL fields))) }) -          -- if we have *all* the field names available, then -          -- keep the record declaration.  Otherwise degrade to -          -- a constructor declaration.  This isn't quite right, but -          -- it's the best we can do. -        InfixCon _ _ -> Just d -      where -        field_avail :: LConDeclField GhcRn -> Bool -        field_avail (L _ (ConDeclField _ fs _ _)) -            = all (\f -> extFieldOcc (unLoc f) `elem` names) fs -        field_types flds = [ hsUnrestricted t | ConDeclField _ _ t _ <- flds ] - -    keep _ = Nothing - -restrictDecls :: [Name] -> [LSig GhcRn] -> [LSig GhcRn] -restrictDecls names = mapMaybe (filterLSigNames (`elem` names)) - - -restrictATs :: [Name] -> [LFamilyDecl GhcRn] -> [LFamilyDecl GhcRn] -restrictATs names ats = [ at | at <- ats , unL (fdLName (unL at)) `elem` names ] - -emptyHsQTvs :: LHsQTyVars GhcRn --- This function is here, rather than in HsTypes, because it *renamed*, but --- does not necessarily have all the rigt kind variables.  It is used --- in Haddock just for printing, so it doesn't matter -emptyHsQTvs = HsQTvs { hsq_ext = error "haddock:emptyHsQTvs" -                     , hsq_explicit = [] } - -  --------------------------------------------------------------------------------  -- * Filename mangling functions stolen from s main/DriverUtil.lhs.  -------------------------------------------------------------------------------- -  baseName :: ModuleName -> FilePath  baseName = map (\c -> if c == '.' then '-' else c) . moduleNameString @@ -252,13 +148,6 @@ indexHtmlFile = "doc-index.html"  indexJsonFile = "doc-index.json" - -moduleIndexFrameName, mainFrameName, synopsisFrameName :: String -moduleIndexFrameName = "modules" -mainFrameName = "main" -synopsisFrameName = "synopsis" - -  subIndexHtmlFile :: String -> String  subIndexHtmlFile ls = "doc-index-" ++ b ++ ".html"     where b | all isAlpha ls = ls @@ -332,7 +221,7 @@ quickJumpCssFile = "quick-jump.css"  getProgramName :: IO String -getProgramName = liftM (`withoutSuffix` ".bin") getProgName +getProgramName = fmap (`withoutSuffix` ".bin") getProgName     where str `withoutSuffix` suff              | suff `isSuffixOf` str = take (length str - length suff) str              | otherwise             = str @@ -341,25 +230,6 @@ getProgramName = liftM (`withoutSuffix` ".bin") getProgName  bye :: String -> IO a  bye s = putStr s >> exitSuccess - -dieMsg :: String -> IO () -dieMsg s = getProgramName >>= \prog -> die (prog ++ ": " ++ s) - - -noDieMsg :: String -> IO () -noDieMsg s = getProgramName >>= \prog -> hPutStr stderr (prog ++ ": " ++ s) - - -mapSnd :: (b -> c) -> [(a,b)] -> [(a,c)] -mapSnd _ [] = [] -mapSnd f ((x,y):xs) = (x,f y) : mapSnd f xs - - -mapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) -mapMaybeM _ Nothing = return Nothing -mapMaybeM f (Just a) = liftM Just (f a) - -  escapeStr :: String -> String  escapeStr = escapeURIString isUnreserved @@ -406,9 +276,9 @@ writeUtf8File filepath contents = withFile filepath WriteMode $ \h -> do      hSetEncoding h utf8      hPutStr h contents -withTempDir :: (ExceptionMonad m) => FilePath -> m a -> m a +withTempDir :: (MonadIO m, MonadMask m) => FilePath -> m a -> m a  withTempDir dir = bracket_ (liftIO $ createDirectory dir) -                            (liftIO $ removeDirectoryRecursive dir) +                           (liftIO $ removeDirectoryRecursive dir)  -----------------------------------------------------------------------------  -- * HTML cross references | 
