From a20b326ff0a7e4ce913af90f5cf968e312891643 Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Thu, 4 Feb 2021 22:33:32 +0100 Subject: Fix after NameCache changes --- haddock-api/src/Documentation/Haddock.hs | 2 - haddock-api/src/Haddock.hs | 21 ++-- haddock-api/src/Haddock/Backends/Hyperlinker.hs | 9 +- haddock-api/src/Haddock/InterfaceFile.hs | 161 +++--------------------- 4 files changed, 36 insertions(+), 157 deletions(-) diff --git a/haddock-api/src/Documentation/Haddock.hs b/haddock-api/src/Documentation/Haddock.hs index 10d6849a..e5d84796 100644 --- a/haddock-api/src/Documentation/Haddock.hs +++ b/haddock-api/src/Documentation/Haddock.hs @@ -52,9 +52,7 @@ module Documentation.Haddock ( -- * Interface files InterfaceFile(..), readInterfaceFile, - nameCacheFromGhc, freshNameCache, - NameCacheAccessor, -- * Flags and options Flag(..), diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 8182707d..d955ae4f 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -71,6 +71,7 @@ import GHC.Settings.Config import GHC.Driver.Session hiding (projectVersion, verbosity) import GHC.Driver.Env import GHC.Utils.Error +import GHC.Types.Name.Cache import GHC.Unit import GHC.Utils.Panic (handleGhcException) import GHC.Data.FastString @@ -188,7 +189,8 @@ haddockWithGhc ghc args = handleTopExceptions $ do unit_state <- hsc_units <$> getSession forM_ (optShowInterfaceFile flags) $ \path -> liftIO $ do - mIfaceFile <- readInterfaceFiles freshNameCache [(("", Nothing), path)] noChecks + name_cache <- freshNameCache + mIfaceFile <- readInterfaceFiles name_cache [(("", Nothing), path)] noChecks forM_ mIfaceFile $ \(_, ifaceFile) -> do putMsg logger dflags $ renderJson (jsonInterfaceFile ifaceFile) @@ -210,7 +212,8 @@ haddockWithGhc ghc args = handleTopExceptions $ do throwE "No input file(s)." -- Get packages supplied with --read-interface. - packages <- liftIO $ readInterfaceFiles freshNameCache (readIfaceArgs flags) noChecks + name_cache <- liftIO $ freshNameCache + packages <- liftIO $ readInterfaceFiles name_cache (readIfaceArgs flags) noChecks -- Render even though there are no input files (usually contents/index). liftIO $ renderStep logger dflags unit_state flags sinceQual qual packages [] @@ -253,7 +256,8 @@ readPackagesAndProcessModules :: [Flag] -> [String] readPackagesAndProcessModules flags files = do -- Get packages supplied with --read-interface. let noChecks = Flag_BypassInterfaceVersonCheck `elem` flags - packages <- readInterfaceFiles nameCacheFromGhc (readIfaceArgs flags) noChecks + name_cache <- hsc_NC <$> getSession + packages <- liftIO $ readInterfaceFiles name_cache (readIfaceArgs flags) noChecks -- Create the interfaces -- this is the core part of Haddock. let ifaceFiles = map snd packages @@ -441,18 +445,17 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS ------------------------------------------------------------------------------- -readInterfaceFiles :: MonadIO m - => NameCacheAccessor m +readInterfaceFiles :: NameCache -> [(DocPaths, FilePath)] -> Bool - -> m [(DocPaths, InterfaceFile)] -readInterfaceFiles name_cache_accessor pairs bypass_version_check = do + -> IO [(DocPaths, InterfaceFile)] +readInterfaceFiles name_cache pairs bypass_version_check = do catMaybes `liftM` mapM ({-# SCC readInterfaceFile #-} tryReadIface) pairs where -- try to read an interface, warn if we can't tryReadIface (paths, file) = - readInterfaceFile name_cache_accessor file bypass_version_check >>= \case - Left err -> liftIO $ do + readInterfaceFile name_cache file bypass_version_check >>= \case + Left err -> do putStrLn ("Warning: Cannot read " ++ file ++ ":") putStrLn (" " ++ err) putStrLn "Skipping this interface." diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs index d16aa24e..39be6762 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs @@ -9,6 +9,7 @@ module Haddock.Backends.Hyperlinker import Haddock.Types import Haddock.Utils (writeUtf8File, out, verbose, Verbosity) +import Haddock.InterfaceFile import Haddock.Backends.Hyperlinker.Renderer import Haddock.Backends.Hyperlinker.Parser import Haddock.Backends.Hyperlinker.Types @@ -20,7 +21,7 @@ import System.Directory import System.FilePath import GHC.Iface.Ext.Types ( pattern HiePath, HieFile(..), HieASTs(..), HieAST(..), SourcedNodeInfo(..) ) -import GHC.Iface.Ext.Binary ( readHieFile, hie_file_result, NameCacheUpdater(..)) +import GHC.Iface.Ext.Binary ( readHieFile, hie_file_result ) import GHC.Types.SrcLoc ( realSrcLocSpan, mkRealSrcLoc ) import Data.Map as M import GHC.Data.FastString ( mkFastString ) @@ -58,15 +59,13 @@ ppHyperlinkedModuleSource :: Verbosity -> FilePath -> Bool -> SrcMaps -> Interfa ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = case ifaceHieFile iface of Just hfp -> do -- Parse the GHC-produced HIE file - u <- mkSplitUniqSupply 'a' - let nc = (initNameCache u []) - ncu = NCU $ \f -> pure $ snd $ f nc + nc <- freshNameCache HieFile { hie_hs_file = file , hie_asts = HieASTs asts , hie_types = types , hie_hs_src = rawSrc } <- hie_file_result - <$> (readHieFile ncu hfp) + <$> (readHieFile nc hfp) -- Get the AST and tokens corresponding to the source file we want let fileFs = mkFastString file diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 211c7d55..7147dc9d 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -16,7 +16,7 @@ ----------------------------------------------------------------------------- module Haddock.InterfaceFile ( InterfaceFile(..), ifUnitId, ifModule, - readInterfaceFile, nameCacheFromGhc, freshNameCache, NameCacheAccessor, + readInterfaceFile, freshNameCache, writeInterfaceFile, binaryInterfaceVersion, binaryInterfaceVersionCompatibility ) where @@ -32,7 +32,7 @@ import qualified Data.Map as Map import Data.Map (Map) import Data.Word -import GHC.Iface.Binary (getSymtabName, getDictFastString) +import GHC.Iface.Binary (getWithUserData, putSymbolTable) import GHC.Utils.Binary import GHC.Data.FastMutInt import GHC.Data.FastString @@ -165,103 +165,32 @@ writeInterfaceFile filename iface = do return () -type NameCacheAccessor m = (m NameCache, NameCache -> m ()) - - -nameCacheFromGhc :: forall m. GhcMonad m => NameCacheAccessor m -nameCacheFromGhc = ( read_from_session , write_to_session ) - where - read_from_session = do - ref <- withSession (return . hsc_NC) - liftIO $ readIORef ref - write_to_session nc' = do - ref <- withSession (return . hsc_NC) - liftIO $ writeIORef ref nc' - - -freshNameCache :: NameCacheAccessor IO -freshNameCache = ( create_fresh_nc , \_ -> return () ) - where - create_fresh_nc = do - u <- mkSplitUniqSupply 'a' -- ?? - return (initNameCache u []) - +freshNameCache :: IO NameCache +freshNameCache = do + u <- mkSplitUniqSupply 'a' -- ?? + initNameCache u [] -- | Read a Haddock (@.haddock@) interface file. Return either an -- 'InterfaceFile' or an error message. -- -- This function can be called in two ways. Within a GHC session it will -- update the use and update the session's name cache. Outside a GHC session --- a new empty name cache is used. The function is therefore generic in the --- monad being used. The exact monad is whichever monad the first --- argument, the getter and setter of the name cache, requires. --- -readInterfaceFile :: forall m. - MonadIO m - => NameCacheAccessor m +-- a new empty name cache is used. +readInterfaceFile :: NameCache -> FilePath -> Bool -- ^ Disable version check. Can cause runtime crash. - -> m (Either String InterfaceFile) -readInterfaceFile (get_name_cache, set_name_cache) filename bypass_checks = do - bh0 <- liftIO $ readBinMem filename - - magic <- liftIO $ get bh0 - version <- liftIO $ get bh0 - - case () of - _ | magic /= binaryInterfaceMagic -> return . Left $ - "Magic number mismatch: couldn't load interface file: " ++ filename - | not bypass_checks - , (version `notElem` binaryInterfaceVersionCompatibility) -> return . Left $ - "Interface file is of wrong version: " ++ filename - | otherwise -> with_name_cache $ \update_nc -> do - - dict <- get_dictionary bh0 - - -- read the symbol table so we are capable of reading the actual data - bh1 <- do - let bh1 = setUserData bh0 $ newReadState (error "getSymtabName") - (getDictFastString dict) - symtab <- update_nc (get_symbol_table bh1) - return $ setUserData bh1 $ newReadState (getSymtabName (NCU (\f -> update_nc (return . f))) dict symtab) - (getDictFastString dict) - - -- load the actual data - iface <- liftIO $ get bh1 - return (Right iface) - where - with_name_cache :: forall a. - ((forall n b. MonadIO n - => (NameCache -> n (NameCache, b)) - -> n b) - -> m a) - -> m a - with_name_cache act = do - nc_var <- get_name_cache >>= (liftIO . newIORef) - x <- act $ \f -> do - nc <- liftIO $ readIORef nc_var - (nc', x) <- f nc - liftIO $ writeIORef nc_var nc' - return x - liftIO (readIORef nc_var) >>= set_name_cache - return x - - get_dictionary bin_handle = liftIO $ do - dict_p <- get bin_handle - data_p <- tellBin bin_handle - seekBin bin_handle dict_p - dict <- getDictionary bin_handle - seekBin bin_handle data_p - return dict - - get_symbol_table bh1 theNC = liftIO $ do - symtab_p <- get bh1 - data_p' <- tellBin bh1 - seekBin bh1 symtab_p - (nc', symtab) <- getSymbolTable bh1 theNC - seekBin bh1 data_p' - return (nc', symtab) - + -> IO (Either String InterfaceFile) +readInterfaceFile name_cache filename bypass_checks = do + bh <- readBinMem filename + + magic <- get bh + if magic /= binaryInterfaceMagic + then return . Left $ "Magic number mismatch: couldn't load interface file: " ++ filename + else do + version <- get bh + if not bypass_checks && (version `notElem` binaryInterfaceVersionCompatibility) + then return . Left $ "Interface file is of wrong version: " ++ filename + else Right <$> getWithUserData name_cache bh ------------------------------------------------------------------------------- -- * Symbol table @@ -312,56 +241,6 @@ data BinDictionary = BinDictionary { -- indexed by FastString } - -putSymbolTable :: BinHandle -> Int -> UniqFM Name (Int,Name) -> IO () -putSymbolTable bh next_off symtab = do - put_ bh next_off - let names = elems (array (0,next_off-1) (eltsUFM symtab)) - mapM_ (\n -> serialiseName bh n symtab) names - - -getSymbolTable :: BinHandle -> NameCache -> IO (NameCache, Array Int Name) -getSymbolTable bh namecache = do - sz <- get bh - od_names <- replicateM sz (get bh) - let arr = listArray (0,sz-1) names - (namecache', names) = mapAccumR (fromOnDiskName arr) namecache od_names - return (namecache', arr) - - -type OnDiskName = (Unit, ModuleName, OccName) - - -fromOnDiskName - :: Array Int Name - -> NameCache - -> OnDiskName - -> (NameCache, Name) -fromOnDiskName _ nc (pid, mod_name, occ) = - let - modu = mkModule pid mod_name - cache = nsNames nc - in - case lookupOrigNameCache cache modu occ of - Just name -> (nc, name) - Nothing -> - let - us = nsUniqs nc - u = uniqFromSupply us - name = mkExternalName u modu occ noSrcSpan - new_cache = extendNameCache cache modu occ name - in - case splitUniqSupply us of { (us',_) -> - ( nc{ nsUniqs = us', nsNames = new_cache }, name ) - } - - -serialiseName :: BinHandle -> Name -> UniqFM Name (Int,Name) -> IO () -serialiseName bh name _ = do - let modu = nameModule name - put_ bh (moduleUnit modu, moduleName modu, nameOccName name) - - ------------------------------------------------------------------------------- -- * GhcBinary instances ------------------------------------------------------------------------------- -- cgit v1.2.3 From adca17adc9f53bb8ab451d0a11911c04145c8fb3 Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Mon, 8 Feb 2021 16:03:17 +0100 Subject: NameCache doesn't store a UniqSupply anymore --- haddock-api/src/Haddock/InterfaceFile.hs | 14 ++------------ hypsrc-test/ref/src/Classes.html | 14 +++++++------- hypsrc-test/ref/src/Records.html | 16 ++++++++-------- 3 files changed, 17 insertions(+), 27 deletions(-) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 7147dc9d..f47e2df0 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -23,11 +23,7 @@ module Haddock.InterfaceFile ( import Haddock.Types -import Control.Monad -import Control.Monad.IO.Class ( MonadIO(..) ) -import Data.Array import Data.IORef -import Data.List (mapAccumR) import qualified Data.Map as Map import Data.Map (Map) import Data.Word @@ -37,13 +33,8 @@ import GHC.Utils.Binary import GHC.Data.FastMutInt import GHC.Data.FastString import GHC hiding (NoLink) -import GHC.Driver.Monad (withSession) -import GHC.Driver.Env import GHC.Types.Name.Cache -import GHC.Iface.Env -import GHC.Types.Name import GHC.Types.Unique.FM -import GHC.Types.Unique.Supply import GHC.Types.Unique data InterfaceFile = InterfaceFile { @@ -166,9 +157,8 @@ writeInterfaceFile filename iface = do freshNameCache :: IO NameCache -freshNameCache = do - u <- mkSplitUniqSupply 'a' -- ?? - initNameCache u [] +freshNameCache = initNameCache 'a' -- ?? + [] -- | Read a Haddock (@.haddock@) interface file. Return either an -- 'InterfaceFile' or an error message. diff --git a/hypsrc-test/ref/src/Classes.html b/hypsrc-test/ref/src/Classes.html index 688b6db6..16d3b333 100644 --- a/hypsrc-test/ref/src/Classes.html +++ b/hypsrc-test/ref/src/Classes.html @@ -194,7 +194,7 @@ >bar :: Int -> Int barbaz :: Int -> (Int, Int) bazbar :: [a] -> Int barbaz :: Int -> ([a], [a]) baznorf :: [Int] -> Int norfquux :: ([a], [a]) -> [a] quuxplugh :: forall a b. Either a a -> Either b b -> Either (a -> b) (b -> a) plughInt -x :: Int x :: Point -> Int +x :: Int xInt -y :: Int y :: Point -> Int +y :: Int yInt -y :: Int -x :: Int -y :: Point -> Int x :: Point -> Int +y :: Point -> Int +x :: Int +y :: Int .. Date: Sat, 20 Mar 2021 03:48:13 +0200 Subject: Specialization of Data.List --- html-test/ref/BundledPatterns.html | 2 +- html-test/ref/BundledPatterns2.html | 2 +- html-test/ref/Identifiers.html | 18 +++++++++--------- hypsrc-test/Main.hs | 2 +- 4 files changed, 12 insertions(+), 12 deletions(-) diff --git a/html-test/ref/BundledPatterns.html b/html-test/ref/BundledPatterns.html index 82f58e49..8ac16a68 100644 --- a/html-test/ref/BundledPatterns.html +++ b/html-test/ref/BundledPatterns.html @@ -152,7 +152,7 @@ > subscript starting from 0 and ending at length - 1 subscript starting from 0 and ending at length - 1++, elemFoldable
  • , ++, elemFoldable, elem
  • Unqualified: 1 `elem``Foldable` [-3..3]
  • Qualified: 1 `elem` [-3..3]
  • Namespaced: `elem``Foldable`, `elem` Date: Wed, 3 Feb 2021 19:10:20 +0100 Subject: Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. --- haddock-api/src/Haddock/Interface.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 02e7ed38..2486c752 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -158,7 +158,7 @@ createIfaces verbosity modules flags instIfaceMap = do -- alive to be able to find all the instances. modifySession installHaddockPlugin - targets <- mapM (\filePath -> guessTarget filePath Nothing) modules + targets <- mapM (\filePath -> guessTarget filePath Nothing Nothing) modules setTargets targets loadOk <- withTimingM "load" (const ()) $ -- cgit v1.2.3 From d8d8024ad6796549a8d3b5512dabf3288d14e30f Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Thu, 25 Mar 2021 21:23:07 +0000 Subject: EPA : Rename ApiAnn to EpAnn --- haddock-api/src/Haddock/GhcUtils.hs | 6 ++--- haddock-api/src/Haddock/Types.hs | 47 +++++++++++++++++-------------------- 2 files changed, 25 insertions(+), 28 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index b8db6dfd..2fc42131 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -338,7 +338,7 @@ reparenTypePrec = go where -- Shorter name for 'reparenType' - go :: XParTy a ~ ApiAnn' AnnParen => Precedence -> HsType a -> HsType a + go :: XParTy a ~ EpAnn' AnnParen => Precedence -> HsType a -> HsType a go _ (HsBangTy x b ty) = HsBangTy x b (reparenLType ty) go _ (HsTupleTy x con tys) = HsTupleTy x con (map reparenLType tys) go _ (HsSumTy x tys) = HsSumTy x (map reparenLType tys) @@ -378,11 +378,11 @@ reparenTypePrec = go go _ t@XHsType{} = t -- Located variant of 'go' - goL :: XParTy a ~ ApiAnn' AnnParen => Precedence -> LHsType a -> LHsType a + goL :: XParTy a ~ EpAnn' AnnParen => Precedence -> LHsType a -> LHsType a goL ctxt_prec = mapXRec @a (go ctxt_prec) -- Optionally wrap a type in parens - paren :: XParTy a ~ ApiAnn' AnnParen + paren :: XParTy a ~ EpAnn' AnnParen => Precedence -- Precedence of context -> Precedence -- Precedence of top-level operator -> HsType a -> HsType a -- Wrap in parens if (ctxt >= op) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 5c6f09a3..d9943e55 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -727,38 +727,35 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA type instance Anno (HsSigType DocNameI) = SrcSpanAnnA type XRecCond a - = ( XParTy a ~ ApiAnn' AnnParen - -- , XParTy (NoGhcTc a) ~ ApiAnn' AnnParen - -- , NoGhcTcPass (NoGhcTcPass a) ~ NoGhcTcPass a - -- , IsPass a + = ( XParTy a ~ EpAnn' AnnParen , NoGhcTc a ~ a , MapXRec a , UnXRec a , WrapXRec a (HsType a) ) -type instance XForAllTy DocNameI = ApiAnn -type instance XQualTy DocNameI = ApiAnn -type instance XTyVar DocNameI = ApiAnn -type instance XStarTy DocNameI = ApiAnn -type instance XAppTy DocNameI = ApiAnn -type instance XAppKindTy DocNameI = ApiAnn -type instance XFunTy DocNameI = ApiAnn -type instance XListTy DocNameI = ApiAnn' AnnParen -type instance XTupleTy DocNameI = ApiAnn' AnnParen -type instance XSumTy DocNameI = ApiAnn' AnnParen -type instance XOpTy DocNameI = ApiAnn -type instance XParTy DocNameI = ApiAnn' AnnParen -type instance XIParamTy DocNameI = ApiAnn -type instance XKindSig DocNameI = ApiAnn +type instance XForAllTy DocNameI = EpAnn +type instance XQualTy DocNameI = EpAnn +type instance XTyVar DocNameI = EpAnn +type instance XStarTy DocNameI = EpAnn +type instance XAppTy DocNameI = EpAnn +type instance XAppKindTy DocNameI = EpAnn +type instance XFunTy DocNameI = EpAnn +type instance XListTy DocNameI = EpAnn' AnnParen +type instance XTupleTy DocNameI = EpAnn' AnnParen +type instance XSumTy DocNameI = EpAnn' AnnParen +type instance XOpTy DocNameI = EpAnn +type instance XParTy DocNameI = EpAnn' AnnParen +type instance XIParamTy DocNameI = EpAnn +type instance XKindSig DocNameI = EpAnn type instance XSpliceTy DocNameI = Void -- see `renameHsSpliceTy` -type instance XDocTy DocNameI = ApiAnn -type instance XBangTy DocNameI = ApiAnn -type instance XRecTy DocNameI = ApiAnn -type instance XExplicitListTy DocNameI = ApiAnn -type instance XExplicitTupleTy DocNameI = ApiAnn -type instance XTyLit DocNameI = ApiAnn -type instance XWildCardTy DocNameI = ApiAnn +type instance XDocTy DocNameI = EpAnn +type instance XBangTy DocNameI = EpAnn +type instance XRecTy DocNameI = EpAnn +type instance XExplicitListTy DocNameI = EpAnn +type instance XExplicitTupleTy DocNameI = EpAnn +type instance XTyLit DocNameI = EpAnn +type instance XWildCardTy DocNameI = EpAnn type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField -- cgit v1.2.3 From 4c471b8ffc5dc59ce72128c1d74818a08c5743cc Mon Sep 17 00:00:00 2001 From: Alfredo Di Napoli Date: Tue, 2 Mar 2021 14:42:31 +0100 Subject: pprError changed name in GHC --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index d9a2e0cd..e6748937 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -14,7 +14,7 @@ import GHC.Types.SourceText import GHC.Driver.Session import GHC.Utils.Error ( pprLocMsgEnvelope ) import GHC.Data.FastString ( mkFastString ) -import GHC.Parser.Errors.Ppr ( pprError ) +import GHC.Parser.Errors.Ppr ( mkParserErr ) import GHC.Parser.Lexer as Lexer ( P(..), ParseResult(..), PState(..), Token(..) , initParserState, lexer, mkParserOpts, getErrorMessages) @@ -40,7 +40,7 @@ parse parse dflags fpath bs = case unP (go False []) initState of POk _ toks -> reverse toks PFailed pst -> - let err:_ = bagToList (fmap pprError (getErrorMessages pst)) in + let err:_ = bagToList (fmap mkParserErr (getErrorMessages pst)) in panic $ showSDoc dflags $ text "Hyperlinker parse error:" $$ pprLocMsgEnvelope err where -- cgit v1.2.3 From dabdee145c8da12aff4eebce7847f2af1a2ddc17 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Sun, 21 Mar 2021 13:07:34 -0400 Subject: Bump GHC version to 9.3 --- haddock-api/src/Haddock/InterfaceFile.hs | 6 +++--- haddock.cabal | 2 +- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index f47e2df0..9c4308a6 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -85,11 +85,11 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if MIN_VERSION_ghc(9,1,0) && !MIN_VERSION_ghc(9,2,0) -binaryInterfaceVersion = 38 +#if MIN_VERSION_ghc(9,3,0) && !MIN_VERSION_ghc(9,4,0) +binaryInterfaceVersion = 39 binaryInterfaceVersionCompatibility :: [Word16] -binaryInterfaceVersionCompatibility = [37, binaryInterfaceVersion] +binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] #else #error Unsupported GHC version #endif diff --git a/haddock.cabal b/haddock.cabal index 1993ead1..65e1aa6b 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -81,7 +81,7 @@ executable haddock xhtml >= 3000.2 && < 3000.3, ghc-boot, ghc-boot-th, - ghc == 9.1.*, + ghc == 9.3.*, bytestring, parsec, text, -- cgit v1.2.3 From 72118896464f94d81f10c52f5d9261efcacc57a6 Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Tue, 11 May 2021 10:00:06 +0200 Subject: Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman --- haddock-api/src/Haddock/Convert.hs | 14 +++++------- haddock-api/src/Haddock/GhcUtils.hs | 6 ++--- haddock-api/src/Haddock/Types.hs | 44 ++++++++++++++++++------------------- 3 files changed, 31 insertions(+), 33 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index 19630077..f8d85f88 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -19,8 +19,6 @@ module Haddock.Convert ( PrintRuntimeReps(..), ) where -#include "HsVersions.h" - import GHC.Data.Bag ( emptyBag ) import GHC.Types.Basic ( TupleSort(..), PromotionFlag(..), DefMethSpec(..), TopLevelFlag(..) ) import GHC.Types.SourceText (SourceText(..)) @@ -47,9 +45,9 @@ import GHC.Builtin.Types ( eqTyConName, listTyConName, liftedTypeKindTyConName import GHC.Builtin.Names ( hasKey, eqTyConKey, ipClassKey, tYPETyConKey , liftedDataConKey, boxedRepDataConKey ) import GHC.Types.Unique ( getUnique ) -import GHC.Utils.Misc ( chkAppend, debugIsOn, dropList, equalLength +import GHC.Utils.Misc ( chkAppend, dropList, equalLength , filterByList, filterOut ) -import GHC.Utils.Panic ( assertPanic ) +import GHC.Utils.Panic.Plain ( assert ) import GHC.Types.Var import GHC.Types.Var.Set import GHC.Types.SrcLoc @@ -933,8 +931,8 @@ tcSplitForAllTysReqPreserveSynonyms :: Type -> ([ReqTVBinder], Type) tcSplitForAllTysReqPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isVisibleArgFlag ty req_bndrs = mapMaybe mk_req_bndr_maybe all_bndrs in - ASSERT( req_bndrs `equalLength` all_bndrs ) - (req_bndrs, body) + assert ( req_bndrs `equalLength` all_bndrs) + (req_bndrs, body) where mk_req_bndr_maybe :: TyCoVarBinder -> Maybe ReqTVBinder mk_req_bndr_maybe (Bndr tv argf) = case argf of @@ -946,8 +944,8 @@ tcSplitForAllTysInvisPreserveSynonyms :: Type -> ([InvisTVBinder], Type) tcSplitForAllTysInvisPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isInvisibleArgFlag ty inv_bndrs = mapMaybe mk_inv_bndr_maybe all_bndrs in - ASSERT( inv_bndrs `equalLength` all_bndrs ) - (inv_bndrs, body) + assert ( inv_bndrs `equalLength` all_bndrs) + (inv_bndrs, body) where mk_inv_bndr_maybe :: TyCoVarBinder -> Maybe InvisTVBinder mk_inv_bndr_maybe (Bndr tv argf) = case argf of diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 2fc42131..1d6b8bc3 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -338,7 +338,7 @@ reparenTypePrec = go where -- Shorter name for 'reparenType' - go :: XParTy a ~ EpAnn' AnnParen => Precedence -> HsType a -> HsType a + go :: XParTy a ~ EpAnn AnnParen => Precedence -> HsType a -> HsType a go _ (HsBangTy x b ty) = HsBangTy x b (reparenLType ty) go _ (HsTupleTy x con tys) = HsTupleTy x con (map reparenLType tys) go _ (HsSumTy x tys) = HsSumTy x (map reparenLType tys) @@ -378,11 +378,11 @@ reparenTypePrec = go go _ t@XHsType{} = t -- Located variant of 'go' - goL :: XParTy a ~ EpAnn' AnnParen => Precedence -> LHsType a -> LHsType a + goL :: XParTy a ~ EpAnn AnnParen => Precedence -> LHsType a -> LHsType a goL ctxt_prec = mapXRec @a (go ctxt_prec) -- Optionally wrap a type in parens - paren :: XParTy a ~ EpAnn' AnnParen + paren :: XParTy a ~ EpAnn AnnParen => Precedence -- Precedence of context -> Precedence -- Precedence of top-level operator -> HsType a -> HsType a -- Wrap in parens if (ctxt >= op) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index d9943e55..7c4aeb80 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -727,35 +727,35 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA type instance Anno (HsSigType DocNameI) = SrcSpanAnnA type XRecCond a - = ( XParTy a ~ EpAnn' AnnParen + = ( XParTy a ~ EpAnn AnnParen , NoGhcTc a ~ a , MapXRec a , UnXRec a , WrapXRec a (HsType a) ) -type instance XForAllTy DocNameI = EpAnn -type instance XQualTy DocNameI = EpAnn -type instance XTyVar DocNameI = EpAnn -type instance XStarTy DocNameI = EpAnn -type instance XAppTy DocNameI = EpAnn -type instance XAppKindTy DocNameI = EpAnn -type instance XFunTy DocNameI = EpAnn -type instance XListTy DocNameI = EpAnn' AnnParen -type instance XTupleTy DocNameI = EpAnn' AnnParen -type instance XSumTy DocNameI = EpAnn' AnnParen -type instance XOpTy DocNameI = EpAnn -type instance XParTy DocNameI = EpAnn' AnnParen -type instance XIParamTy DocNameI = EpAnn -type instance XKindSig DocNameI = EpAnn +type instance XForAllTy DocNameI = EpAnn [AddEpAnn] +type instance XQualTy DocNameI = EpAnn [AddEpAnn] +type instance XTyVar DocNameI = EpAnn [AddEpAnn] +type instance XStarTy DocNameI = EpAnn [AddEpAnn] +type instance XAppTy DocNameI = EpAnn [AddEpAnn] +type instance XAppKindTy DocNameI = EpAnn [AddEpAnn] +type instance XFunTy DocNameI = EpAnn [AddEpAnn] +type instance XListTy DocNameI = EpAnn AnnParen +type instance XTupleTy DocNameI = EpAnn AnnParen +type instance XSumTy DocNameI = EpAnn AnnParen +type instance XOpTy DocNameI = EpAnn [AddEpAnn] +type instance XParTy DocNameI = EpAnn AnnParen +type instance XIParamTy DocNameI = EpAnn [AddEpAnn] +type instance XKindSig DocNameI = EpAnn [AddEpAnn] type instance XSpliceTy DocNameI = Void -- see `renameHsSpliceTy` -type instance XDocTy DocNameI = EpAnn -type instance XBangTy DocNameI = EpAnn -type instance XRecTy DocNameI = EpAnn -type instance XExplicitListTy DocNameI = EpAnn -type instance XExplicitTupleTy DocNameI = EpAnn -type instance XTyLit DocNameI = EpAnn -type instance XWildCardTy DocNameI = EpAnn +type instance XDocTy DocNameI = EpAnn [AddEpAnn] +type instance XBangTy DocNameI = EpAnn [AddEpAnn] +type instance XRecTy DocNameI = EpAnn [AddEpAnn] +type instance XExplicitListTy DocNameI = EpAnn [AddEpAnn] +type instance XExplicitTupleTy DocNameI = EpAnn [AddEpAnn] +type instance XTyLit DocNameI = EpAnn [AddEpAnn] +type instance XWildCardTy DocNameI = EpAnn [AddEpAnn] type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField -- cgit v1.2.3 From bbaa3dfbf6ea4e0ad1356622ce7750ba76076b7d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?H=C3=A9cate=20Moonlight?= Date: Tue, 11 May 2021 10:14:47 +0200 Subject: Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. --- haddock-api/src/Haddock/Convert.hs | 14 +++++++----- haddock-api/src/Haddock/GhcUtils.hs | 6 ++--- haddock-api/src/Haddock/Types.hs | 44 ++++++++++++++++++------------------- 3 files changed, 33 insertions(+), 31 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index f8d85f88..19630077 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -19,6 +19,8 @@ module Haddock.Convert ( PrintRuntimeReps(..), ) where +#include "HsVersions.h" + import GHC.Data.Bag ( emptyBag ) import GHC.Types.Basic ( TupleSort(..), PromotionFlag(..), DefMethSpec(..), TopLevelFlag(..) ) import GHC.Types.SourceText (SourceText(..)) @@ -45,9 +47,9 @@ import GHC.Builtin.Types ( eqTyConName, listTyConName, liftedTypeKindTyConName import GHC.Builtin.Names ( hasKey, eqTyConKey, ipClassKey, tYPETyConKey , liftedDataConKey, boxedRepDataConKey ) import GHC.Types.Unique ( getUnique ) -import GHC.Utils.Misc ( chkAppend, dropList, equalLength +import GHC.Utils.Misc ( chkAppend, debugIsOn, dropList, equalLength , filterByList, filterOut ) -import GHC.Utils.Panic.Plain ( assert ) +import GHC.Utils.Panic ( assertPanic ) import GHC.Types.Var import GHC.Types.Var.Set import GHC.Types.SrcLoc @@ -931,8 +933,8 @@ tcSplitForAllTysReqPreserveSynonyms :: Type -> ([ReqTVBinder], Type) tcSplitForAllTysReqPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isVisibleArgFlag ty req_bndrs = mapMaybe mk_req_bndr_maybe all_bndrs in - assert ( req_bndrs `equalLength` all_bndrs) - (req_bndrs, body) + ASSERT( req_bndrs `equalLength` all_bndrs ) + (req_bndrs, body) where mk_req_bndr_maybe :: TyCoVarBinder -> Maybe ReqTVBinder mk_req_bndr_maybe (Bndr tv argf) = case argf of @@ -944,8 +946,8 @@ tcSplitForAllTysInvisPreserveSynonyms :: Type -> ([InvisTVBinder], Type) tcSplitForAllTysInvisPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isInvisibleArgFlag ty inv_bndrs = mapMaybe mk_inv_bndr_maybe all_bndrs in - assert ( inv_bndrs `equalLength` all_bndrs) - (inv_bndrs, body) + ASSERT( inv_bndrs `equalLength` all_bndrs ) + (inv_bndrs, body) where mk_inv_bndr_maybe :: TyCoVarBinder -> Maybe InvisTVBinder mk_inv_bndr_maybe (Bndr tv argf) = case argf of diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 1d6b8bc3..2fc42131 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -338,7 +338,7 @@ reparenTypePrec = go where -- Shorter name for 'reparenType' - go :: XParTy a ~ EpAnn AnnParen => Precedence -> HsType a -> HsType a + go :: XParTy a ~ EpAnn' AnnParen => Precedence -> HsType a -> HsType a go _ (HsBangTy x b ty) = HsBangTy x b (reparenLType ty) go _ (HsTupleTy x con tys) = HsTupleTy x con (map reparenLType tys) go _ (HsSumTy x tys) = HsSumTy x (map reparenLType tys) @@ -378,11 +378,11 @@ reparenTypePrec = go go _ t@XHsType{} = t -- Located variant of 'go' - goL :: XParTy a ~ EpAnn AnnParen => Precedence -> LHsType a -> LHsType a + goL :: XParTy a ~ EpAnn' AnnParen => Precedence -> LHsType a -> LHsType a goL ctxt_prec = mapXRec @a (go ctxt_prec) -- Optionally wrap a type in parens - paren :: XParTy a ~ EpAnn AnnParen + paren :: XParTy a ~ EpAnn' AnnParen => Precedence -- Precedence of context -> Precedence -- Precedence of top-level operator -> HsType a -> HsType a -- Wrap in parens if (ctxt >= op) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 7c4aeb80..d9943e55 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -727,35 +727,35 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA type instance Anno (HsSigType DocNameI) = SrcSpanAnnA type XRecCond a - = ( XParTy a ~ EpAnn AnnParen + = ( XParTy a ~ EpAnn' AnnParen , NoGhcTc a ~ a , MapXRec a , UnXRec a , WrapXRec a (HsType a) ) -type instance XForAllTy DocNameI = EpAnn [AddEpAnn] -type instance XQualTy DocNameI = EpAnn [AddEpAnn] -type instance XTyVar DocNameI = EpAnn [AddEpAnn] -type instance XStarTy DocNameI = EpAnn [AddEpAnn] -type instance XAppTy DocNameI = EpAnn [AddEpAnn] -type instance XAppKindTy DocNameI = EpAnn [AddEpAnn] -type instance XFunTy DocNameI = EpAnn [AddEpAnn] -type instance XListTy DocNameI = EpAnn AnnParen -type instance XTupleTy DocNameI = EpAnn AnnParen -type instance XSumTy DocNameI = EpAnn AnnParen -type instance XOpTy DocNameI = EpAnn [AddEpAnn] -type instance XParTy DocNameI = EpAnn AnnParen -type instance XIParamTy DocNameI = EpAnn [AddEpAnn] -type instance XKindSig DocNameI = EpAnn [AddEpAnn] +type instance XForAllTy DocNameI = EpAnn +type instance XQualTy DocNameI = EpAnn +type instance XTyVar DocNameI = EpAnn +type instance XStarTy DocNameI = EpAnn +type instance XAppTy DocNameI = EpAnn +type instance XAppKindTy DocNameI = EpAnn +type instance XFunTy DocNameI = EpAnn +type instance XListTy DocNameI = EpAnn' AnnParen +type instance XTupleTy DocNameI = EpAnn' AnnParen +type instance XSumTy DocNameI = EpAnn' AnnParen +type instance XOpTy DocNameI = EpAnn +type instance XParTy DocNameI = EpAnn' AnnParen +type instance XIParamTy DocNameI = EpAnn +type instance XKindSig DocNameI = EpAnn type instance XSpliceTy DocNameI = Void -- see `renameHsSpliceTy` -type instance XDocTy DocNameI = EpAnn [AddEpAnn] -type instance XBangTy DocNameI = EpAnn [AddEpAnn] -type instance XRecTy DocNameI = EpAnn [AddEpAnn] -type instance XExplicitListTy DocNameI = EpAnn [AddEpAnn] -type instance XExplicitTupleTy DocNameI = EpAnn [AddEpAnn] -type instance XTyLit DocNameI = EpAnn [AddEpAnn] -type instance XWildCardTy DocNameI = EpAnn [AddEpAnn] +type instance XDocTy DocNameI = EpAnn +type instance XBangTy DocNameI = EpAnn +type instance XRecTy DocNameI = EpAnn +type instance XExplicitListTy DocNameI = EpAnn +type instance XExplicitTupleTy DocNameI = EpAnn +type instance XTyLit DocNameI = EpAnn +type instance XWildCardTy DocNameI = EpAnn type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField -- cgit v1.2.3 From 07663b5e69b038b811d213701cba322e90e6f212 Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Thu, 15 Apr 2021 20:57:21 +0100 Subject: Update for EPA changes in GHC --- haddock-api/src/Haddock/GhcUtils.hs | 6 ++--- haddock-api/src/Haddock/Types.hs | 44 ++++++++++++++++++------------------- 2 files changed, 25 insertions(+), 25 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 2fc42131..1d6b8bc3 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -338,7 +338,7 @@ reparenTypePrec = go where -- Shorter name for 'reparenType' - go :: XParTy a ~ EpAnn' AnnParen => Precedence -> HsType a -> HsType a + go :: XParTy a ~ EpAnn AnnParen => Precedence -> HsType a -> HsType a go _ (HsBangTy x b ty) = HsBangTy x b (reparenLType ty) go _ (HsTupleTy x con tys) = HsTupleTy x con (map reparenLType tys) go _ (HsSumTy x tys) = HsSumTy x (map reparenLType tys) @@ -378,11 +378,11 @@ reparenTypePrec = go go _ t@XHsType{} = t -- Located variant of 'go' - goL :: XParTy a ~ EpAnn' AnnParen => Precedence -> LHsType a -> LHsType a + goL :: XParTy a ~ EpAnn AnnParen => Precedence -> LHsType a -> LHsType a goL ctxt_prec = mapXRec @a (go ctxt_prec) -- Optionally wrap a type in parens - paren :: XParTy a ~ EpAnn' AnnParen + paren :: XParTy a ~ EpAnn AnnParen => Precedence -- Precedence of context -> Precedence -- Precedence of top-level operator -> HsType a -> HsType a -- Wrap in parens if (ctxt >= op) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index d9943e55..7c4aeb80 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -727,35 +727,35 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA type instance Anno (HsSigType DocNameI) = SrcSpanAnnA type XRecCond a - = ( XParTy a ~ EpAnn' AnnParen + = ( XParTy a ~ EpAnn AnnParen , NoGhcTc a ~ a , MapXRec a , UnXRec a , WrapXRec a (HsType a) ) -type instance XForAllTy DocNameI = EpAnn -type instance XQualTy DocNameI = EpAnn -type instance XTyVar DocNameI = EpAnn -type instance XStarTy DocNameI = EpAnn -type instance XAppTy DocNameI = EpAnn -type instance XAppKindTy DocNameI = EpAnn -type instance XFunTy DocNameI = EpAnn -type instance XListTy DocNameI = EpAnn' AnnParen -type instance XTupleTy DocNameI = EpAnn' AnnParen -type instance XSumTy DocNameI = EpAnn' AnnParen -type instance XOpTy DocNameI = EpAnn -type instance XParTy DocNameI = EpAnn' AnnParen -type instance XIParamTy DocNameI = EpAnn -type instance XKindSig DocNameI = EpAnn +type instance XForAllTy DocNameI = EpAnn [AddEpAnn] +type instance XQualTy DocNameI = EpAnn [AddEpAnn] +type instance XTyVar DocNameI = EpAnn [AddEpAnn] +type instance XStarTy DocNameI = EpAnn [AddEpAnn] +type instance XAppTy DocNameI = EpAnn [AddEpAnn] +type instance XAppKindTy DocNameI = EpAnn [AddEpAnn] +type instance XFunTy DocNameI = EpAnn [AddEpAnn] +type instance XListTy DocNameI = EpAnn AnnParen +type instance XTupleTy DocNameI = EpAnn AnnParen +type instance XSumTy DocNameI = EpAnn AnnParen +type instance XOpTy DocNameI = EpAnn [AddEpAnn] +type instance XParTy DocNameI = EpAnn AnnParen +type instance XIParamTy DocNameI = EpAnn [AddEpAnn] +type instance XKindSig DocNameI = EpAnn [AddEpAnn] type instance XSpliceTy DocNameI = Void -- see `renameHsSpliceTy` -type instance XDocTy DocNameI = EpAnn -type instance XBangTy DocNameI = EpAnn -type instance XRecTy DocNameI = EpAnn -type instance XExplicitListTy DocNameI = EpAnn -type instance XExplicitTupleTy DocNameI = EpAnn -type instance XTyLit DocNameI = EpAnn -type instance XWildCardTy DocNameI = EpAnn +type instance XDocTy DocNameI = EpAnn [AddEpAnn] +type instance XBangTy DocNameI = EpAnn [AddEpAnn] +type instance XRecTy DocNameI = EpAnn [AddEpAnn] +type instance XExplicitListTy DocNameI = EpAnn [AddEpAnn] +type instance XExplicitTupleTy DocNameI = EpAnn [AddEpAnn] +type instance XTyLit DocNameI = EpAnn [AddEpAnn] +type instance XWildCardTy DocNameI = EpAnn [AddEpAnn] type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField -- cgit v1.2.3 From ef2304bbff1e30fcd9306b5b211f045d608753c0 Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Thu, 6 May 2021 22:29:36 +0200 Subject: Account for HsVersions.h removal --- haddock-api/src/Haddock/Convert.hs | 14 ++++++-------- 1 file changed, 6 insertions(+), 8 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index 19630077..f8d85f88 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -19,8 +19,6 @@ module Haddock.Convert ( PrintRuntimeReps(..), ) where -#include "HsVersions.h" - import GHC.Data.Bag ( emptyBag ) import GHC.Types.Basic ( TupleSort(..), PromotionFlag(..), DefMethSpec(..), TopLevelFlag(..) ) import GHC.Types.SourceText (SourceText(..)) @@ -47,9 +45,9 @@ import GHC.Builtin.Types ( eqTyConName, listTyConName, liftedTypeKindTyConName import GHC.Builtin.Names ( hasKey, eqTyConKey, ipClassKey, tYPETyConKey , liftedDataConKey, boxedRepDataConKey ) import GHC.Types.Unique ( getUnique ) -import GHC.Utils.Misc ( chkAppend, debugIsOn, dropList, equalLength +import GHC.Utils.Misc ( chkAppend, dropList, equalLength , filterByList, filterOut ) -import GHC.Utils.Panic ( assertPanic ) +import GHC.Utils.Panic.Plain ( assert ) import GHC.Types.Var import GHC.Types.Var.Set import GHC.Types.SrcLoc @@ -933,8 +931,8 @@ tcSplitForAllTysReqPreserveSynonyms :: Type -> ([ReqTVBinder], Type) tcSplitForAllTysReqPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isVisibleArgFlag ty req_bndrs = mapMaybe mk_req_bndr_maybe all_bndrs in - ASSERT( req_bndrs `equalLength` all_bndrs ) - (req_bndrs, body) + assert ( req_bndrs `equalLength` all_bndrs) + (req_bndrs, body) where mk_req_bndr_maybe :: TyCoVarBinder -> Maybe ReqTVBinder mk_req_bndr_maybe (Bndr tv argf) = case argf of @@ -946,8 +944,8 @@ tcSplitForAllTysInvisPreserveSynonyms :: Type -> ([InvisTVBinder], Type) tcSplitForAllTysInvisPreserveSynonyms ty = let (all_bndrs, body) = tcSplitSomeForAllTysPreserveSynonyms isInvisibleArgFlag ty inv_bndrs = mapMaybe mk_inv_bndr_maybe all_bndrs in - ASSERT( inv_bndrs `equalLength` all_bndrs ) - (inv_bndrs, body) + assert ( inv_bndrs `equalLength` all_bndrs) + (inv_bndrs, body) where mk_inv_bndr_maybe :: TyCoVarBinder -> Maybe InvisTVBinder mk_inv_bndr_maybe (Bndr tv argf) = case argf of -- cgit v1.2.3 From a1337c599ef7720b0482a25c55f11794112496dc Mon Sep 17 00:00:00 2001 From: Christiaan Baaij Date: Thu, 13 May 2021 08:21:56 +0200 Subject: Add Haddock support for the OPAQUE pragma (#1380) --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index e6748937..f4bc038c 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -233,6 +233,7 @@ classify tok = ITrequires -> TkKeyword ITinline_prag {} -> TkPragma + ITopaque_prag {} -> TkPragma ITspec_prag {} -> TkPragma ITspec_inline_prag {} -> TkPragma ITsource_prag {} -> TkPragma @@ -374,6 +375,7 @@ inPragma True _ = True inPragma False tok = case tok of ITinline_prag {} -> True + ITopaque_prag {} -> True ITspec_prag {} -> True ITspec_inline_prag {} -> True ITsource_prag {} -> True -- cgit v1.2.3 From 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2 Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Thu, 13 May 2021 19:04:33 +0100 Subject: EPA: match changes from GHC T19834 --- haddock-api/src/Haddock/Convert.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index f8d85f88..3a7ef57d 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -209,7 +209,7 @@ synifyTyCon prr _coax tc , tcdFixity = synifyFixity tc - , tcdDataDefn = HsDataDefn { dd_ext = noAnn + , tcdDataDefn = HsDataDefn { dd_ext = noExtField , dd_ND = DataType -- arbitrary lie, they are neither -- algebraic data nor newtype: , dd_ctxt = Nothing @@ -300,7 +300,7 @@ synifyTyCon _prr coax tc cons = rights consRaw -- "deriving" doesn't affect the signature, no need to specify any. alg_deriv = [] - defn = HsDataDefn { dd_ext = noAnn + defn = HsDataDefn { dd_ext = noExtField , dd_ND = alg_nd , dd_ctxt = alg_ctx , dd_cType = Nothing -- cgit v1.2.3 From 212f5302995cae9884aff924f0d53597bd77e9c2 Mon Sep 17 00:00:00 2001 From: Divam Narula Date: Thu, 20 May 2021 22:42:42 +0900 Subject: Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. --- html-test/ref/Instances.html | 50 ++++++++++++++++++++++---------------------- 1 file changed, 25 insertions(+), 25 deletions(-) diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html index 9e9f2300..e99f82e4 100644 --- a/html-test/ref/Instances.html +++ b/html-test/ref/Instances.html @@ -1300,9 +1300,9 @@ >baz :: [c] -> (forall a. a -> a) -> (b, a1. a1 -> a1) -> (b, forall c0. c0 -> [c]) -> (b, c1) c1. c1 -> [c]) -> (b, c0) #

    baz' :: b -> (forall b. b -> [c]) -> ( b1. b1 -> [c]) -> (forall b. b -> [c]) -> [(b, [c])] b1. b1 -> [c]) -> [(b, [c])] #

    baz'' :: b -> (forall b. ( b1. (forall b. b -> [c]) -> c0) -> b2. b2 -> [c]) -> c0) -> forall c1. c1 -> b #baz :: (a -> b) -> (forall a0. a0 -> a0) -> (b0, a1. a1 -> a1) -> (b0, forall c. c -> a -> b) -> (b0, c) c1. c1 -> a -> b) -> (b0, c) #

    forall b1. b1 -> a -> b) -> (forall b2. b2 -> a -> b) -> [(b0, a -> b)] b1. b1 -> a -> b) -> [(b0, a -> b)] #

    forall b2. b2 -> a -> b) -> c) -> forall c. c -> b0 c1. c1 -> b0 #

    Quux a b c -> (forall a0. a0 -> a0) -> (b0, a1. a1 -> a1) -> (b0, forall c0. c0 -> c1. c1 -> Quux a b c) -> (b0, c1) a b c) -> (b0, c0) #

    Quux a b c) -> (forall b2. b2 -> b1. b1 -> Quux a b c) -> [(b0, Quuxbaz :: (a, b, c) -> (forall a0. a0 -> a0) -> (b0, a1. a1 -> a1) -> (b0, forall c0. c0 -> (a, b, c)) -> (b0, c1) c1. c1 -> (a, b, c)) -> (b0, c0) #

    forall b1. b1 -> (a, b, c)) -> (forall b2. b2 -> (a, b, c)) -> [(b0, (a, b, c))] b1. b1 -> (a, b, c)) -> [(b0, (a, b, c))] #

    baz :: (a, [b], b, a) -> (forall a0. a0 -> a0) -> (b0, a1. a1 -> a1) -> (b0, forall c. c -> (a, [b], b, a)) -> (b0, c) c1. c1 -> (a, [b], b, a)) -> (b0, c) #

    forall b1. b1 -> (a, [b], b, a)) -> (forall b2. b2 -> (a, [b], b, a)) -> [(b0, (a, [b], b, a))] b1. b1 -> (a, [b], b, a)) -> [(b0, (a, [b], b, a))] #

    forall b2. b2 -> (a, [b], b, a)) -> c) -> forall c. c -> b0 c1. c1 -> b0 #

    Quux a b c -> (forall a0. a0 -> a0) -> (b0, a1. a1 -> a1) -> (b0, forall c0. c0 -> c1. c1 -> Quux a b c) -> (b0, c1) a b c) -> (b0, c0) #

    Quux a b c) -> (forall b2. b2 -> b1. b1 -> Quux a b c) -> [(b0, Quux Date: Sun, 16 May 2021 21:21:03 +0100 Subject: Remove Maybe from HsQualTy Match changes in GHC for #19845 --- haddock-api/src/Haddock/Backends/Hoogle.hs | 2 +- haddock-api/src/Haddock/Backends/LaTeX.hs | 13 +++++++------ haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 16 +++++++++------- haddock-api/src/Haddock/Convert.hs | 10 +++++----- haddock-api/src/Haddock/GhcUtils.hs | 11 ++++------- haddock-api/src/Haddock/Interface/Create.hs | 4 ++-- haddock-api/src/Haddock/Interface/Rename.hs | 2 +- haddock-api/src/Haddock/Interface/Specialize.hs | 9 ++++----- 8 files changed, 33 insertions(+), 34 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index e70a705f..3f913e09 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -280,7 +280,7 @@ ppCtor dflags _dat subdocs (ConDeclGADT { con_names = names name = out dflags $ map unL names con_sig_ty = HsSig noExtField outer_bndrs theta_ty where theta_ty = case mcxt of - Just theta -> noLocA (HsQualTy { hst_xqual = noExtField, hst_ctxt = Just theta, hst_body = tau_ty }) + Just theta -> noLocA (HsQualTy { hst_xqual = noExtField, hst_ctxt = theta, hst_body = tau_ty }) Nothing -> tau_ty tau_ty = foldr mkFunTy res_ty $ case args of PrefixConGADT pos_args -> map hsScaledThing pos_args diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index abf882f0..fbae13a3 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -983,11 +983,12 @@ ppTypeApp n ts ppDN ppT = ppDN n <+> hsep (map ppT ts) ------------------------------------------------------------------------------- -ppLContext, ppLContextNoArrow :: Maybe (LHsContext DocNameI) -> Bool -> LaTeX -ppLContext Nothing _ = empty -ppLContext (Just ctxt) unicode = ppContext (unLoc ctxt) unicode -ppLContextNoArrow Nothing _ = empty -ppLContextNoArrow (Just ctxt) unicode = ppContextNoArrow (unLoc ctxt) unicode +ppLContext :: Maybe (LHsContext DocNameI) -> Bool -> LaTeX +ppLContext Nothing _ = empty +ppLContext (Just ctxt) unicode = ppContext (unLoc ctxt) unicode + +ppLContextNoArrow :: LHsContext DocNameI -> Bool -> LaTeX +ppLContextNoArrow ctxt unicode = ppContextNoArrow (unLoc ctxt) unicode ppContextNoLocsMaybe :: [HsType DocNameI] -> Bool -> Maybe LaTeX ppContextNoLocsMaybe [] _ = Nothing @@ -1101,7 +1102,7 @@ ppr_mono_ty (HsForAllTy _ tele ty) unicode = sep [ ppHsForAllTelescope tele unicode , ppr_mono_lty ty unicode ] ppr_mono_ty (HsQualTy _ ctxt ty) unicode - = sep [ ppLContext ctxt unicode + = sep [ ppLContext (Just ctxt) unicode , ppr_mono_lty ty unicode ] ppr_mono_ty (HsFunTy _ mult ty1 ty2) u = sep [ ppr_mono_lty ty1 u diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 8de1b1b8..8ac1ac81 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -167,7 +167,7 @@ ppSubSigLike unicode qual typ argDocs subdocs sep emptyCtxts = do_sig_args 0 sep leader' = leader <+> ppForAllPart unicode qual tele do_args n leader (HsQualTy _ lctxt ltype) - | null (fromMaybeContext lctxt) + | null (unLoc lctxt) = do_largs n leader ltype | otherwise = (leader <+> ppLContextNoArrow lctxt unicode qual emptyCtxts, Nothing, []) @@ -436,12 +436,14 @@ ppTypeApp n ts ppDN ppT = ppDN Prefix n <+> hsep (map ppT ts) ------------------------------------------------------------------------------- -ppLContext, ppLContextNoArrow :: Maybe (LHsContext DocNameI) -> Unicode +ppLContext :: Maybe (LHsContext DocNameI) -> Unicode -> Qualification -> HideEmptyContexts -> Html ppLContext Nothing u q h = ppContext [] u q h ppLContext (Just c) u q h = ppContext (unLoc c) u q h -ppLContextNoArrow Nothing u q h = ppContextNoArrow [] u q h -ppLContextNoArrow (Just c) u q h = ppContextNoArrow (unLoc c) u q h + +ppLContextNoArrow :: LHsContext DocNameI -> Unicode + -> Qualification -> HideEmptyContexts -> Html +ppLContextNoArrow c u q h = ppContextNoArrow (unLoc c) u q h ppContextNoArrow :: HsContext DocNameI -> Unicode -> Qualification -> HideEmptyContexts -> Html ppContextNoArrow cxt unicode qual emptyCtxts = fromMaybe noHtml $ @@ -1185,13 +1187,13 @@ patSigContext sig_typ | hasNonEmptyContext typ && isFirstContextEmpty typ = Sho hasNonEmptyContext t = case unLoc t of HsForAllTy _ _ s -> hasNonEmptyContext s - HsQualTy _ cxt s -> if null (fromMaybeContext cxt) then hasNonEmptyContext s else True + HsQualTy _ cxt s -> if null (unLoc cxt) then hasNonEmptyContext s else True HsFunTy _ _ _ s -> hasNonEmptyContext s _ -> False isFirstContextEmpty t = case unLoc t of HsForAllTy _ _ s -> isFirstContextEmpty s - HsQualTy _ cxt _ -> null (fromMaybeContext cxt) + HsQualTy _ cxt _ -> null (unLoc cxt) HsFunTy _ _ _ s -> isFirstContextEmpty s _ -> False @@ -1230,7 +1232,7 @@ ppr_mono_ty (HsForAllTy _ tele ty) unicode qual emptyCtxts = ppForAllPart unicode qual tele <+> ppr_mono_lty ty unicode qual emptyCtxts ppr_mono_ty (HsQualTy _ ctxt ty) unicode qual emptyCtxts - = ppLContext ctxt unicode qual emptyCtxts <+> ppr_mono_lty ty unicode qual emptyCtxts + = ppLContext (Just ctxt) unicode qual emptyCtxts <+> ppr_mono_lty ty unicode qual emptyCtxts -- UnicodeSyntax alternatives ppr_mono_ty (HsTyVar _ _ (L _ name)) True _ _ diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index 3a7ef57d..a2bdb1b9 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -124,7 +124,7 @@ tyThingToLHsDecl prr t = case t of vs = tyConVisibleTyVars (classTyCon cl) in withErrs (lefts atTyClDecls) . TyClD noExtField $ ClassDecl - { tcdCtxt = synifyCtx (classSCTheta cl) + { tcdCtxt = Just $ synifyCtx (classSCTheta cl) , tcdLName = synifyNameN cl , tcdTyVars = synifyTyVars vs , tcdFixity = synifyFixity cl @@ -302,7 +302,7 @@ synifyTyCon _prr coax tc alg_deriv = [] defn = HsDataDefn { dd_ext = noExtField , dd_ND = alg_nd - , dd_ctxt = alg_ctx + , dd_ctxt = Just alg_ctx , dd_cType = Nothing , dd_kindSig = kindSig , dd_cons = cons @@ -375,7 +375,7 @@ synifyDataCon use_gadt_syntax dc = -- skip any EqTheta, use 'orig'inal syntax ctx | null theta = Nothing - | otherwise = synifyCtx theta + | otherwise = Just $ synifyCtx theta linear_tys = zipWith (\ty bang -> @@ -462,8 +462,8 @@ synifyTcIdSig vs (i, dm) = mainSig t = synifySigType DeleteTopLevelQuantification vs t defSig t = synifySigType ImplicitizeForAll vs t -synifyCtx :: [PredType] -> Maybe (LHsContext GhcRn) -synifyCtx ts = Just (noLocA ( map (synifyType WithinType []) ts)) +synifyCtx :: [PredType] -> LHsContext GhcRn +synifyCtx ts = noLocA ( map (synifyType WithinType []) ts) synifyTyVars :: [TyVar] -> LHsQTyVars GhcRn diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 1d6b8bc3..9353708a 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -171,7 +171,7 @@ getGADTConType (ConDeclGADT { con_bndrs = L _ outer_bndrs , sig_body = theta_ty }) where theta_ty | Just theta <- mcxt - = noLocA (HsQualTy { hst_xqual = noAnn, hst_ctxt = Just theta, hst_body = tau_ty }) + = noLocA (HsQualTy { hst_xqual = noAnn, hst_ctxt = theta, hst_body = tau_ty }) | otherwise = tau_ty @@ -226,12 +226,11 @@ addClassContext cls tvs0 (L pos (ClassOpSig _ _ lname ltype)) , hst_ctxt = add_ctxt ctxt, hst_body = ty }) go_ty (L loc ty) = L loc (HsQualTy { hst_xqual = noExtField - , hst_ctxt = add_ctxt Nothing, hst_body = L loc ty }) + , hst_ctxt = add_ctxt (noLocA []), hst_body = L loc ty }) extra_pred = nlHsTyConApp Prefix cls (lHsQTyVarsToTypes tvs0) - add_ctxt Nothing = Just $ noLocA [extra_pred] - add_ctxt (Just (L loc preds)) = Just $ L loc (extra_pred : preds) + add_ctxt (L loc preds) = L loc (extra_pred : preds) addClassContext _ _ sig = sig -- E.g. a MinimalSig is fine @@ -356,9 +355,7 @@ reparenTypePrec = go go p (HsQualTy x ctxt ty) = let p' [_] = PREC_CTX p' _ = PREC_TOP -- parens will get added anyways later... - ctxt' = case ctxt of - Nothing -> Nothing - Just c -> Just $ mapXRec @a (\xs -> map (goL (p' xs)) xs) c + ctxt' = mapXRec @a (\xs -> map (goL (p' xs)) xs) ctxt in paren p PREC_CTX $ HsQualTy x ctxt' (goL PREC_TOP ty) -- = paren p PREC_FUN $ HsQualTy x (fmap (mapXRec @a (map reparenLType)) ctxt) (reparenLType ty) go p (HsFunTy x w ty1 ty2) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index a280c0b2..4f689532 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1146,9 +1146,9 @@ extractPatternSyn nm t tvs cons = typ = longArrow args (data_ty con) typ' = case con of - ConDeclH98 { con_mb_cxt = Just cxt } -> noLocA (HsQualTy noExtField (Just cxt) typ) + ConDeclH98 { con_mb_cxt = Just cxt } -> noLocA (HsQualTy noExtField cxt typ) _ -> typ - typ'' = noLocA (HsQualTy noExtField Nothing typ') + typ'' = noLocA (HsQualTy noExtField (noLocA []) typ') in PatSynSig noAnn [noLocA nm] (mkEmptySigType typ'') longArrow :: [LHsType GhcRn] -> LHsType GhcRn -> LHsType GhcRn diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 2833df49..693a22ef 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -258,7 +258,7 @@ renameType t = case t of , hst_tele = tele', hst_body = ltype' }) HsQualTy { hst_ctxt = lcontext , hst_body = ltype } -> do - lcontext' <- traverse renameLContext lcontext + lcontext' <- renameLContext lcontext ltype' <- renameLType ltype return (HsQualTy { hst_xqual = noAnn, hst_ctxt = lcontext', hst_body = ltype' }) diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index 16f00fda..657da7ae 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -283,7 +283,7 @@ renameType (HsForAllTy x tele lt) = <*> renameLType lt renameType (HsQualTy x lctxt lt) = HsQualTy x - <$> renameMContext lctxt + <$> renameLContext lctxt <*> renameLType lt renameType (HsTyVar x ip name) = HsTyVar x ip <$> locatedN renameName name renameType t@(HsStarTy _ _) = pure t @@ -324,11 +324,10 @@ renameLKind = renameLType renameLTypes :: [LHsType GhcRn] -> Rename (IdP GhcRn) [LHsType GhcRn] renameLTypes = mapM renameLType -renameMContext :: Maybe (LHsContext GhcRn) -> Rename (IdP GhcRn) (Maybe (LHsContext GhcRn)) -renameMContext Nothing = return Nothing -renameMContext (Just (L l ctxt)) = do +renameLContext :: LHsContext GhcRn -> Rename (IdP GhcRn) (LHsContext GhcRn) +renameLContext (L l ctxt) = do ctxt' <- renameContext ctxt - return (Just (L l ctxt')) + return (L l ctxt') renameContext :: HsContext GhcRn -> Rename (IdP GhcRn) (HsContext GhcRn) renameContext = renameLTypes -- cgit v1.2.3 From 3b6a8774bdb543dad59b2618458b07feab8a55e9 Mon Sep 17 00:00:00 2001 From: Shayne Fletcher Date: Sat, 24 Apr 2021 14:31:41 -0400 Subject: FieldOcc: rename extFieldOcc to foExt --- haddock-api/src/Haddock/Backends/Hoogle.hs | 4 ++-- haddock-api/src/Haddock/Backends/LaTeX.hs | 4 ++-- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 6 +++--- haddock-api/src/Haddock/GhcUtils.hs | 4 ++-- haddock-api/src/Haddock/Interface/Create.hs | 4 ++-- 5 files changed, 11 insertions(+), 11 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 3f913e09..38d378e2 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -247,8 +247,8 @@ ppCtor dflags dat subdocs con@ConDeclH98 { con_args = con_args' } f (PrefixCon _ args) = [typeSig name $ (map hsScaledThing args) ++ [resType]] f (InfixCon a1 a2) = f $ PrefixCon [] [a1,a2] f (RecCon (L _ recs)) = f (PrefixCon [] $ map (hsLinear . cd_fld_type . unLoc) recs) ++ concat - [(concatMap (lookupCon dflags subdocs . noLocA . extFieldOcc . unLoc) (cd_fld_names r)) ++ - [out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]] + [(concatMap (lookupCon dflags subdocs . noLocA . foExt . unLoc) (cd_fld_names r)) ++ + [out dflags (map (foExt . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]] | r <- map unLoc recs] funs = foldr1 (\x y -> reL $ HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) x y) diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index fbae13a3..c7ba5a80 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -887,12 +887,12 @@ ppSideBySideConstr subdocs unicode leader (L _ con) = -- | Pretty-print a record field ppSideBySideField :: [(DocName, DocForDecl DocName)] -> Bool -> ConDeclField DocNameI -> LaTeX ppSideBySideField subdocs unicode (ConDeclField _ names ltype _) = - decltt (cat (punctuate comma (map (ppBinder . rdrNameOcc . unLoc . rdrNameFieldOcc . unLoc) names)) + decltt (cat (punctuate comma (map (ppBinder . rdrNameOcc . unLoc . foLabel . unLoc) names)) <+> dcolon unicode <+> ppLType unicode ltype) <-> rDoc mbDoc where -- don't use cd_fld_doc for same reason we don't use con_doc above -- Where there is more than one name, they all have the same documentation - mbDoc = lookup (extFieldOcc $ unLoc $ head names) subdocs >>= fmap _doc . combineDocumentation . fst + mbDoc = lookup (foExt $ unLoc $ head names) subdocs >>= fmap _doc . combineDocumentation . fst -- | Pretty-print a bundled pattern synonym diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 8ac1ac81..994b5d0d 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -1027,7 +1027,7 @@ ppSideBySideField :: [(DocName, DocForDecl DocName)] -> Unicode -> Qualification ppSideBySideField subdocs unicode qual (ConDeclField _ names ltype _) = ( hsep (punctuate comma [ ppBinder False (rdrNameOcc field) | L _ name <- names - , let field = (unLoc . rdrNameFieldOcc) name + , let field = (unLoc . foLabel) name ]) <+> dcolon unicode <+> ppLType unicode qual HideEmptyContexts ltype @@ -1037,12 +1037,12 @@ ppSideBySideField subdocs unicode qual (ConDeclField _ names ltype _) = where -- don't use cd_fld_doc for same reason we don't use con_doc above -- Where there is more than one name, they all have the same documentation - mbDoc = lookup (extFieldOcc $ unLoc $ head names) subdocs >>= combineDocumentation . fst + mbDoc = lookup (foExt $ unLoc $ head names) subdocs >>= combineDocumentation . fst ppShortField :: Bool -> Unicode -> Qualification -> ConDeclField DocNameI -> Html ppShortField summary unicode qual (ConDeclField _ names ltype _) - = hsep (punctuate comma (map ((ppBinder summary) . rdrNameOcc . unLoc . rdrNameFieldOcc . unLoc) names)) + = hsep (punctuate comma (map ((ppBinder summary) . rdrNameOcc . unLoc . foLabel . unLoc) names)) <+> dcolon unicode <+> ppLType unicode qual HideEmptyContexts ltype diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 9353708a..fa567da8 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -290,7 +290,7 @@ restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ] where field_avail :: LConDeclField GhcRn -> Bool field_avail (L _ (ConDeclField _ fs _ _)) - = all (\f -> extFieldOcc (unLoc f) `elem` names) fs + = all (\f -> foExt (unLoc f) `elem` names) fs field_types flds = [ hsUnrestricted t | L _ (ConDeclField _ _ t _) <- flds ] @@ -466,7 +466,7 @@ instance Parent (ConDecl GhcRn) where children con = case getRecConArgs_maybe con of Nothing -> [] - Just flds -> map (extFieldOcc . unLoc) $ concatMap (cd_fld_names . unLoc) (unLoc flds) + Just flds -> map (foExt . unLoc) $ concatMap (cd_fld_names . unLoc) (unLoc flds) instance Parent (TyClDecl GhcRn) where children d diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 4f689532..2d79bb97 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1113,7 +1113,7 @@ extractDecl declMap name decl , Just rec <- map (getRecConArgs_maybe . unLoc) (dd_cons (feqn_rhs d)) , ConDeclField { cd_fld_names = ns } <- map unLoc (unLoc rec) , L _ n <- ns - , extFieldOcc n == name + , foExt n == name ] in case matches of [d0] -> extractDecl declMap name (noLocA . InstD noExtField $ DataFamInstD noExtField d0) @@ -1174,7 +1174,7 @@ extractRecSel nm t tvs (L _ con : rest) = where matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)] matching_fields flds = [ (l,f) | f@(L _ (ConDeclField _ ns _ _)) <- flds - , L l n <- ns, extFieldOcc n == nm ] + , L l n <- ns, foExt n == nm ] data_ty -- ResTyGADT _ ty <- con_res con = ty | ConDeclGADT{} <- con = con_res_ty con -- cgit v1.2.3 From 40ba457f6436b7eb2c60e8824e1591526945df2a Mon Sep 17 00:00:00 2001 From: Alfredo Di Napoli Date: Mon, 26 Apr 2021 12:56:50 +0200 Subject: New Parser diagnostics interface --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index e6748937..94395218 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -12,9 +12,10 @@ import qualified Data.ByteString as BS import GHC.Types.SourceText import GHC.Driver.Session -import GHC.Utils.Error ( pprLocMsgEnvelope ) +import GHC.Utils.Error ( mkPlainMsgEnvelope, pprLocMsgEnvelope ) import GHC.Data.FastString ( mkFastString ) -import GHC.Parser.Errors.Ppr ( mkParserErr ) +import GHC.Parser.Errors.Ppr () +import qualified GHC.Types.Error as E import GHC.Parser.Lexer as Lexer ( P(..), ParseResult(..), PState(..), Token(..) , initParserState, lexer, mkParserOpts, getErrorMessages) @@ -40,7 +41,7 @@ parse parse dflags fpath bs = case unP (go False []) initState of POk _ toks -> reverse toks PFailed pst -> - let err:_ = bagToList (fmap mkParserErr (getErrorMessages pst)) in + let err:_ = bagToList (E.getMessages $ getErrorMessages pst) in panic $ showSDoc dflags $ text "Hyperlinker parse error:" $$ pprLocMsgEnvelope err where @@ -50,6 +51,7 @@ parse dflags fpath bs = case unP (go False []) initState of start = mkRealSrcLoc (mkFastString fpath) 1 1 pflags = mkParserOpts (warningFlags dflags) (extensionFlags dflags) + (mkPlainMsgEnvelope dflags) (safeImportsOn dflags) False -- lex Haddocks as comment tokens True -- produce comment tokens -- cgit v1.2.3 From 4f9088e4b04e52ca510b55a78048c9230537e449 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Mon, 24 May 2021 11:19:01 -0400 Subject: Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index d5ee7420..94395218 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -235,7 +235,6 @@ classify tok = ITrequires -> TkKeyword ITinline_prag {} -> TkPragma - ITopaque_prag {} -> TkPragma ITspec_prag {} -> TkPragma ITspec_inline_prag {} -> TkPragma ITsource_prag {} -> TkPragma @@ -377,7 +376,6 @@ inPragma True _ = True inPragma False tok = case tok of ITinline_prag {} -> True - ITopaque_prag {} -> True ITspec_prag {} -> True ITspec_inline_prag {} -> True ITsource_prag {} -> True -- cgit v1.2.3 From c120839debadd7a1427cee84459c01d59c5b85aa Mon Sep 17 00:00:00 2001 From: Ben Simms Date: Fri, 28 May 2021 06:56:20 +0100 Subject: CI configuration for ghc-head (#1395) --- .github/workflows/ci.yml | 16 ++++++++++------ cabal.project | 11 +++++++++-- haddock-api/haddock-api.cabal | 2 +- haddock-library/fixtures/Fixtures.hs | 3 +-- haddock-library/haddock-library.cabal | 6 ++---- .../test/Documentation/Haddock/Parser/UtilSpec.hs | 2 +- 6 files changed, 24 insertions(+), 16 deletions(-) diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index b2b882e3..c2aa9f3c 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -4,7 +4,7 @@ name: CI on: pull_request: push: - branches: ["ghc-9.0"] + branches: ["ghc-head"] jobs: cabal: @@ -13,15 +13,20 @@ jobs: strategy: matrix: os: [ubuntu-latest] - cabal: ["3.4"] + cabal: ["3.4.0.0"] ghc: - - "9.0.1" + - "head" steps: - uses: actions/checkout@v2 - if: github.event.action == 'opened' || github.event.action == 'synchronize' || github.event.ref == 'refs/heads/ghc-9.0' + if: github.event.action == 'opened' || github.event.action == 'synchronize' || github.event.ref == 'refs/heads/ghc-head' - - uses: haskell/actions/setup@v1 + - name: Install gmp and tinfo + run: | + sudo -- sh -c "apt-get update" + sudo -- sh -c "apt-get -y install libgmp-dev libtinfo-dev" + + - uses: haskell/actions/setup@main id: setup-haskell-cabal name: Setup Haskell with: @@ -31,7 +36,6 @@ jobs: - name: Prepare environment run: echo "$HOME/.ghcup/bin" >> $GITHUB_PATH - - name: Freeze run: | cabal freeze diff --git a/cabal.project b/cabal.project index 2525070a..1b5a2732 100644 --- a/cabal.project +++ b/cabal.project @@ -3,12 +3,19 @@ packages: ./ ./haddock-library ./haddock-test -with-compiler: ghc-9.0 +with-compiler: ghc-head allow-newer: ghc-paths:Cabal, *:base, - *:ghc-prim + *:ghc-prim, + tree-diff:time + +package haddock-library + tests: False + +package haddock-api + tests: False -- Pinning the index-state helps to make reasonably CI deterministic index-state: 2021-01-24T12:09:34Z diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index 730f4f5c..feecf40a 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -44,7 +44,7 @@ library -- this package typically supports only single major versions build-depends: base ^>= 4.16.0 - , ghc ^>= 9.1 + , ghc ^>= 9.3 , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.9.0 , xhtml ^>= 3000.2.2 diff --git a/haddock-library/fixtures/Fixtures.hs b/haddock-library/fixtures/Fixtures.hs index 101bce65..374a664c 100644 --- a/haddock-library/fixtures/Fixtures.hs +++ b/haddock-library/fixtures/Fixtures.hs @@ -9,8 +9,7 @@ import Data.Foldable (traverse_) import Data.List (foldl') import Data.Traversable (for) import GHC.Generics (Generic) -import Prelude () -import Prelude.Compat +import Prelude import System.Directory (getDirectoryContents) import System.Exit (exitFailure) import System.FilePath diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 490dff10..72c11f75 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -39,7 +39,7 @@ common lib-defaults build-depends: , base >= 4.5 && < 4.17 - , bytestring ^>= 0.9.2.1 || ^>= 0.10.0.0 + , bytestring ^>= 0.9.2.1 || ^>= 0.10.0.0 || ^>= 0.11.0.0 , containers ^>= 0.4.2.1 || ^>= 0.5.0.0 || ^>= 0.6.0.1 , transformers ^>= 0.3.0.0 || ^>= 0.4.1.0 || ^>= 0.5.0.0 , text ^>= 1.2.3.0 @@ -87,8 +87,7 @@ test-suite spec Documentation.Haddock.Parser.Identifier build-depends: - , base-compat ^>= 0.9.3 || ^>= 0.11.0 - , QuickCheck ^>= 2.11 || ^>= 2.13.2 || ^>= 2.14 + , QuickCheck ^>= 2.11 || ^>= 2.13.2 || ^>= 2.14 , deepseq ^>= 1.3.0.0 || ^>= 1.4.0.0 -- NB: build-depends & build-tool-depends have independent @@ -114,7 +113,6 @@ test-suite fixtures , base -- extra dependencies - , base-compat ^>= 0.9.3 || ^>= 0.11.0 , directory ^>= 1.3.0.2 , filepath ^>= 1.4.1.2 , optparse-applicative ^>= 0.15 diff --git a/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs b/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs index 10c701c7..cb991763 100644 --- a/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs +++ b/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs @@ -3,7 +3,7 @@ module Documentation.Haddock.Parser.UtilSpec (main, spec) where import Documentation.Haddock.Parser.Monad import Documentation.Haddock.Parser.Util -import Data.Either.Compat (isLeft) +import Data.Either (isLeft) import Test.Hspec import Control.Applicative -- cgit v1.2.3 From 1ceb34bf20ef4f226a4152264505826d3138957e Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Tue, 1 Jun 2021 10:02:06 +0200 Subject: Adapt Haddock to Logger and Parser changes (#1399) --- haddock-api/src/Haddock.hs | 17 ++++++++++------- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 3 +++ haddock-api/src/Haddock/Interface.hs | 14 +++++--------- haddock-api/src/Haddock/Parser.hs | 2 +- 4 files changed, 19 insertions(+), 17 deletions(-) diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index d955ae4f..9158d83c 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -69,8 +69,10 @@ import Text.ParserCombinators.ReadP (readP_to_S) import GHC hiding (verbosity) import GHC.Settings.Config import GHC.Driver.Session hiding (projectVersion, verbosity) +import GHC.Driver.Config.Logger (initLogFlags) import GHC.Driver.Env import GHC.Utils.Error +import GHC.Utils.Logger import GHC.Types.Name.Cache import GHC.Unit import GHC.Utils.Panic (handleGhcException) @@ -192,7 +194,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do name_cache <- freshNameCache mIfaceFile <- readInterfaceFiles name_cache [(("", Nothing), path)] noChecks forM_ mIfaceFile $ \(_, ifaceFile) -> do - putMsg logger dflags $ renderJson (jsonInterfaceFile ifaceFile) + putMsg logger $ renderJson (jsonInterfaceFile ifaceFile) if not (null files) then do (packages, ifaces, homeLinks) <- readPackagesAndProcessModules flags files @@ -282,7 +284,7 @@ renderStep logger dflags unit_state flags sinceQual nameQual pkgs interfaces = d -- | Render the interfaces with whatever backend is specified in the flags. render :: Logger -> DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption -> [Interface] -> [InstalledInterface] -> Map Module FilePath -> IO () -render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do +render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do let title = fromMaybe "" (optTitle flags) @@ -298,6 +300,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS dflags' | unicode = gopt_set dflags Opt_PrintUnicodeSyntax | otherwise = dflags + logger = setLogFlags log' (initLogFlags dflags') visibleIfaces = [ i | i <- ifaces, OptHide `notElem` ifaceOptions i ] @@ -372,7 +375,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS let withQuickjump = Flag_QuickJumpIndex `elem` flags when (Flag_GenIndex `elem` flags) $ do - withTiming logger dflags' "ppHtmlIndex" (const ()) $ do + withTiming logger "ppHtmlIndex" (const ()) $ do _ <- {-# SCC ppHtmlIndex #-} ppHtmlIndex odir title pkgStr themes opt_mathjax opt_contents_url sourceUrls' opt_wiki_urls @@ -382,7 +385,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS copyHtmlBits odir libDir themes withQuickjump when (Flag_GenContents `elem` flags) $ do - withTiming logger dflags' "ppHtmlContents" (const ()) $ do + withTiming logger "ppHtmlContents" (const ()) $ do _ <- {-# SCC ppHtmlContents #-} ppHtmlContents unit_state odir title pkgStr themes opt_mathjax opt_index_url sourceUrls' opt_wiki_urls @@ -392,7 +395,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS copyHtmlBits odir libDir themes withQuickjump when (Flag_Html `elem` flags) $ do - withTiming logger dflags' "ppHtml" (const ()) $ do + withTiming logger "ppHtml" (const ()) $ do _ <- {-# SCC ppHtml #-} ppHtml unit_state title pkgStr visibleIfaces reexportedIfaces odir prologue @@ -427,14 +430,14 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS ] when (Flag_LaTeX `elem` flags) $ do - withTiming logger dflags' "ppLatex" (const ()) $ do + withTiming logger "ppLatex" (const ()) $ do _ <- {-# SCC ppLatex #-} ppLaTeX title pkgStr visibleIfaces odir (fmap _doc prologue) opt_latex_style libDir return () when (Flag_HyperlinkedSource `elem` flags && not (null ifaces)) $ do - withTiming logger dflags' "ppHyperlinkedSource" (const ()) $ do + withTiming logger "ppHyperlinkedSource" (const ()) $ do _ <- {-# SCC ppHyperlinkedSource #-} ppHyperlinkedSource (verbosity flags) odir libDir opt_source_css pretty srcMap ifaces return () diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 94395218..49e2c66f 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -10,6 +10,7 @@ import Data.List ( isPrefixOf, isSuffixOf ) import qualified Data.ByteString as BS +import GHC.Platform import GHC.Types.SourceText import GHC.Driver.Session import GHC.Utils.Error ( mkPlainMsgEnvelope, pprLocMsgEnvelope ) @@ -49,9 +50,11 @@ parse dflags fpath bs = case unP (go False []) initState of initState = initParserState pflags buf start buf = stringBufferFromByteString bs start = mkRealSrcLoc (mkFastString fpath) 1 1 + arch_os = platformArchOS (targetPlatform dflags) pflags = mkParserOpts (warningFlags dflags) (extensionFlags dflags) (mkPlainMsgEnvelope dflags) + (supportedLanguagesAndExtensions arch_os) (safeImportsOn dflags) False -- lex Haddocks as comment tokens True -- produce comment tokens diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 2486c752..2e9b2f7e 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -56,7 +56,7 @@ import qualified Data.Set as Set import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed (flattenSCCs) -import GHC.Driver.Env (hsc_dflags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) +import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs (getMainDeclBinder) @@ -145,11 +145,8 @@ createIfaces verbosity modules flags instIfaceMap = do let installHaddockPlugin :: HscEnv -> HscEnv - installHaddockPlugin hsc_env = hsc_env - { - hsc_dflags = - gopt_set (hsc_dflags hsc_env) Opt_PluginTrustworthy - , hsc_static_plugins = + installHaddockPlugin hsc_env = hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) $ hsc_env + { hsc_static_plugins = haddockPlugin : hsc_static_plugins hsc_env } @@ -212,7 +209,7 @@ plugin verbosity flags instIfaceMap = liftIO $ do | otherwise = do hsc_env <- getTopEnv ifaces <- liftIO $ readIORef ifaceMapRef - (iface, modules) <- withTiming (hsc_logger hsc_env) (hsc_dflags hsc_env) + (iface, modules) <- withTiming (hsc_logger hsc_env) "processModule" (const ()) $ processModule1 verbosity flags ifaces instIfaceMap hsc_env mod_summary tc_gbl_env @@ -266,9 +263,8 @@ processModule1 verbosity flags ifaces inst_ifaces hsc_env mod_summary tc_gbl_env (!interface, messages) <- do logger <- getLogger - dflags <- getDynFlags {-# SCC createInterface #-} - withTiming logger dflags "createInterface" (const ()) $ runIfM (fmap Just . tcLookupGlobal) $ + withTiming logger "createInterface" (const ()) $ runIfM (fmap Just . tcLookupGlobal) $ createInterface1 flags unit_state mod_summary tc_gbl_env ifaces inst_ifaces diff --git a/haddock-api/src/Haddock/Parser.hs b/haddock-api/src/Haddock/Parser.hs index ab2fa549..53cf98ad 100644 --- a/haddock-api/src/Haddock/Parser.hs +++ b/haddock-api/src/Haddock/Parser.hs @@ -19,7 +19,7 @@ import Documentation.Haddock.Types import Haddock.Types import GHC.Driver.Session ( DynFlags ) -import GHC.Driver.Config +import GHC.Driver.Config.Parser (initParserOpts) import GHC.Data.FastString ( fsLit ) import GHC.Parser.Lexer ( initParserState, unP, ParseResult(POk, PFailed) ) import GHC.Parser ( parseIdentifier ) -- cgit v1.2.3 From f1464f981ba8119a25f61104127a67df6c42321f Mon Sep 17 00:00:00 2001 From: wz1000 Date: Wed, 2 Jun 2021 00:15:10 +0530 Subject: Update haddockHypSrc tests since we now compute slighly more type info (#1397) --- hypsrc-test/ref/src/UsingQuasiquotes.html | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/hypsrc-test/ref/src/UsingQuasiquotes.html b/hypsrc-test/ref/src/UsingQuasiquotes.html index 1e7aef2c..b3ce68ec 100644 --- a/hypsrc-test/ref/src/UsingQuasiquotes.html +++ b/hypsrc-test/ref/src/UsingQuasiquotes.html @@ -78,7 +78,10 @@ > [Char] +[string| foo bar |] [Char] +[string| some mulitline quasiquote -- cgit v1.2.3 From caee7fce3032ac08c38a591de5e31f37eedf681f Mon Sep 17 00:00:00 2001 From: Ben Simms Date: Wed, 2 Jun 2021 18:47:14 +0100 Subject: Update CONTRIBUTING.md (#1403) --- CONTRIBUTING.md | 15 ++++++--------- 1 file changed, 6 insertions(+), 9 deletions(-) diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md index 1e1aeca6..af7a414f 100644 --- a/CONTRIBUTING.md +++ b/CONTRIBUTING.md @@ -44,20 +44,17 @@ so that documentation built within GHC can benefit from it. #### Using `cabal` -Requires cabal `>= 3.4` and GHC `== 9.0`: +Requires cabal `>= 3.4` and the latest build of GHC: + +You can install the latest build of GHC via ghcup using this command: ```bash -cabal v2-build all --enable-tests -cabal v2-test all +ghcup install ghc -u "https://gitlab.haskell.org/ghc/ghc/-/jobs/artifacts/master/raw/ghc-x86_64-deb9-linux-integer-simple.tar.xz?job=validate-x86_64-linux-deb9-integer-simple" head ``` -#### Using `stack` - ```bash -stack init -stack build -export HADDOCK_PATH="$(stack exec which haddock)" -stack test +cabal v2-build all --enable-tests +cabal v2-test all ``` ### Updating golden testsuite outputs -- cgit v1.2.3 From 126beaef07cdcbe8aeea248cc555e8a3057de82b Mon Sep 17 00:00:00 2001 From: sheaf Date: Mon, 31 May 2021 21:31:16 +0200 Subject: Update Haddock Bug873 to account for renaming --- hoogle-test/ref/Bug873/test.txt | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/hoogle-test/ref/Bug873/test.txt b/hoogle-test/ref/Bug873/test.txt index 68873317..5e1117a4 100644 --- a/hoogle-test/ref/Bug873/test.txt +++ b/hoogle-test/ref/Bug873/test.txt @@ -18,9 +18,9 @@ module Bug873 -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. -- --- Note that ($) is levity-polymorphic in its result --- type, so that foo $ True where foo :: Bool -> --- Int# is well-typed. +-- Note that ($) is representation-polymorphic in its +-- result type, so that foo $ True where foo :: Bool +-- -> Int# is well-typed. ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 $ ($$) :: (a -> b) -> a -> b -- cgit v1.2.3 From 0029f289bec7427032785f13cf3bcdebddf7b91f Mon Sep 17 00:00:00 2001 From: Vladislav Zavialov Date: Tue, 1 Jun 2021 10:31:12 +0300 Subject: HsToken in FunTy, RecConGADT --- haddock-api/src/Haddock/Backends/Hoogle.hs | 6 +++--- haddock-api/src/Haddock/Backends/LaTeX.hs | 6 +++--- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 6 +++--- haddock-api/src/Haddock/Convert.hs | 8 ++++---- haddock-api/src/Haddock/GhcUtils.hs | 6 +++--- haddock-api/src/Haddock/Interface/Create.hs | 6 +++--- haddock-api/src/Haddock/Interface/Rename.hs | 11 ++++++----- haddock-api/src/Haddock/Interface/Specialize.hs | 4 ++-- 8 files changed, 27 insertions(+), 26 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 38d378e2..dfb167a3 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -251,7 +251,7 @@ ppCtor dflags dat subdocs con@ConDeclH98 { con_args = con_args' } [out dflags (map (foExt . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]] | r <- map unLoc recs] - funs = foldr1 (\x y -> reL $ HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) x y) + funs = foldr1 (\x y -> reL $ HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) x y) apps = foldl1 (\x y -> reL $ HsAppTy noExtField x y) typeSig nm flds = operator nm ++ " :: " ++ @@ -284,8 +284,8 @@ ppCtor dflags _dat subdocs (ConDeclGADT { con_names = names Nothing -> tau_ty tau_ty = foldr mkFunTy res_ty $ case args of PrefixConGADT pos_args -> map hsScaledThing pos_args - RecConGADT (L _ flds) -> map (cd_fld_type . unL) flds - mkFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) a b) + RecConGADT (L _ flds) _ -> map (cd_fld_type . unL) flds + mkFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) a b) ppFixity :: DynFlags -> (Name, Fixity) -> [String] ppFixity dflags (name, fixity) = [out dflags ((FixitySig noExtField [noLocA name] fixity) :: FixitySig GhcRn)] diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index c7ba5a80..eb524ec7 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -843,7 +843,7 @@ ppSideBySideConstr subdocs unicode leader (L _ con) = fieldPart = case con of ConDeclGADT{con_g_args = con_args'} -> case con_args' of -- GADT record declarations - RecConGADT _ -> doConstrArgsWithDocs [] + RecConGADT _ _ -> doConstrArgsWithDocs [] -- GADT prefix data constructors PrefixConGADT args | hasArgDocs -> doConstrArgsWithDocs (map hsScaledThing args) _ -> empty @@ -1108,9 +1108,9 @@ ppr_mono_ty (HsFunTy _ mult ty1 ty2) u = sep [ ppr_mono_lty ty1 u , arr <+> ppr_mono_lty ty2 u ] where arr = case mult of - HsLinearArrow _ _ -> lollipop u + HsLinearArrow _ -> lollipop u HsUnrestrictedArrow _ -> arrow u - HsExplicitMult _ _ m -> multAnnotation <> ppr_mono_lty m u <+> arrow u + HsExplicitMult _ m _ -> multAnnotation <> ppr_mono_lty m u <+> arrow u ppr_mono_ty (HsBangTy _ b ty) u = ppBang b <> ppLParendType u ty ppr_mono_ty (HsTyVar _ NotPromoted (L _ name)) _ = ppDocName name diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 994b5d0d..336f23ac 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -969,7 +969,7 @@ ppSideBySideConstr subdocs fixities unicode pkg qual (L _ con) fieldPart = case con of ConDeclGADT{con_g_args = con_args'} -> case con_args' of -- GADT record declarations - RecConGADT _ -> [ doConstrArgsWithDocs [] ] + RecConGADT _ _ -> [ doConstrArgsWithDocs [] ] -- GADT prefix data constructors PrefixConGADT args | hasArgDocs -> [ doConstrArgsWithDocs args ] _ -> [] @@ -1250,9 +1250,9 @@ ppr_mono_ty (HsFunTy _ mult ty1 ty2) u q e = , arr <+> ppr_mono_lty ty2 u q e ] where arr = case mult of - HsLinearArrow _ _ -> lollipop u + HsLinearArrow _ -> lollipop u HsUnrestrictedArrow _ -> arrow u - HsExplicitMult _ _ m -> multAnnotation <> ppr_mono_lty m u q e <+> arrow u + HsExplicitMult _ m _ -> multAnnotation <> ppr_mono_lty m u q e <+> arrow u ppr_mono_ty (HsTupleTy _ con tys) u q _ = tupleParens con (map (ppLType u q HideEmptyContexts) tys) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index a2bdb1b9..cf533c20 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -401,7 +401,7 @@ synifyDataCon use_gadt_syntax dc = mk_gadt_arg_tys :: HsConDeclGADTDetails GhcRn mk_gadt_arg_tys - | use_named_field_syntax = RecConGADT (noLocA field_tys) + | use_named_field_syntax = RecConGADT (noLocA field_tys) noHsUniTok | otherwise = PrefixConGADT (map hsUnrestricted linear_tys) -- finally we get synifyDataCon's result! @@ -797,9 +797,9 @@ noKindTyVars _ _ = emptyVarSet synifyMult :: [TyVar] -> Mult -> HsArrow GhcRn synifyMult vs t = case t of - One -> HsLinearArrow NormalSyntax Nothing - Many -> HsUnrestrictedArrow NormalSyntax - ty -> HsExplicitMult NormalSyntax Nothing (synifyType WithinType vs ty) + One -> HsLinearArrow (HsPct1 noHsTok noHsUniTok) + Many -> HsUnrestrictedArrow noHsUniTok + ty -> HsExplicitMult noHsTok (synifyType WithinType vs ty) noHsUniTok diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index fa567da8..599404a0 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -177,11 +177,11 @@ getGADTConType (ConDeclGADT { con_bndrs = L _ outer_bndrs -- tau_ty :: LHsType DocNameI tau_ty = case args of - RecConGADT flds -> mkFunTy (noLocA (HsRecTy noAnn (unLoc flds))) res_ty + RecConGADT flds _ -> mkFunTy (noLocA (HsRecTy noAnn (unLoc flds))) res_ty PrefixConGADT pos_args -> foldr mkFunTy res_ty (map hsScaledThing pos_args) mkFunTy :: LHsType DocNameI -> LHsType DocNameI -> LHsType DocNameI - mkFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) a b) + mkFunTy a b = noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) a b) getGADTConType (ConDeclH98 {}) = panic "getGADTConType" -- Should only be called on ConDeclGADT @@ -283,7 +283,7 @@ restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ] ConDeclGADT { con_g_args = con_args' } -> case con_args' of PrefixConGADT {} -> Just d - RecConGADT fields + RecConGADT fields _ | all field_avail (unLoc fields) -> Just d | otherwise -> Just (d { con_g_args = PrefixConGADT (field_types $ unLoc fields) }) -- see above diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 2d79bb97..2782f711 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1142,7 +1142,7 @@ extractPatternSyn nm t tvs cons = InfixCon arg1 arg2 -> map hsScaledThing [arg1, arg2] ConDeclGADT { con_g_args = con_args' } -> case con_args' of PrefixConGADT args' -> map hsScaledThing args' - RecConGADT (L _ fields) -> cd_fld_type . unLoc <$> fields + RecConGADT (L _ fields) _ -> cd_fld_type . unLoc <$> fields typ = longArrow args (data_ty con) typ' = case con of @@ -1152,7 +1152,7 @@ extractPatternSyn nm t tvs cons = in PatSynSig noAnn [noLocA nm] (mkEmptySigType typ'') longArrow :: [LHsType GhcRn] -> LHsType GhcRn -> LHsType GhcRn - longArrow inputs output = foldr (\x y -> noLocA (HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) x y)) output inputs + longArrow inputs output = foldr (\x y -> noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) x y)) output inputs data_ty con | ConDeclGADT{} <- con = con_res_ty con @@ -1169,7 +1169,7 @@ extractRecSel _ _ _ [] = Left "extractRecSel: selector not found" extractRecSel nm t tvs (L _ con : rest) = case getRecConArgs_maybe con of Just (L _ fields) | ((l,L _ (ConDeclField _ _nn ty _)) : _) <- matching_fields fields -> - pure (L (noAnnSrcSpan l) (TypeSig noAnn [noLocA nm] (mkEmptyWildCardBndrs $ mkEmptySigType (noLocA (HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) data_ty (getBangType ty)))))) + pure (L (noAnnSrcSpan l) (TypeSig noAnn [noLocA nm] (mkEmptyWildCardBndrs $ mkEmptySigType (noLocA (HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) data_ty (getBangType ty)))))) _ -> extractRecSel nm t tvs rest where matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)] diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 693a22ef..98b3a6e6 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -245,9 +245,10 @@ renameMaybeInjectivityAnn :: Maybe (LInjectivityAnn GhcRn) renameMaybeInjectivityAnn = traverse renameInjectivityAnn renameArrow :: HsArrow GhcRn -> RnM (HsArrow DocNameI) -renameArrow (HsUnrestrictedArrow u) = return (HsUnrestrictedArrow u) -renameArrow (HsLinearArrow u a) = return (HsLinearArrow u a) -renameArrow (HsExplicitMult u a p) = HsExplicitMult u a <$> renameLType p +renameArrow (HsUnrestrictedArrow arr) = return (HsUnrestrictedArrow arr) +renameArrow (HsLinearArrow (HsPct1 pct1 arr)) = return (HsLinearArrow (HsPct1 pct1 arr)) +renameArrow (HsLinearArrow (HsLolly arr)) = return (HsLinearArrow (HsLolly arr)) +renameArrow (HsExplicitMult pct p arr) = (\p' -> HsExplicitMult pct p' arr) <$> renameLType p renameType :: HsType GhcRn -> RnM (HsType DocNameI) renameType t = case t of @@ -548,9 +549,9 @@ renameH98Details (InfixCon a b) = do renameGADTDetails :: HsConDeclGADTDetails GhcRn -> RnM (HsConDeclGADTDetails DocNameI) -renameGADTDetails (RecConGADT (L l fields)) = do +renameGADTDetails (RecConGADT (L l fields) arr) = do fields' <- mapM renameConDeclFieldField fields - return (RecConGADT (L (locA l) fields')) + return (RecConGADT (L (locA l) fields') arr) renameGADTDetails (PrefixConGADT ps) = PrefixConGADT <$> mapM renameHsScaled ps renameConDeclFieldField :: LConDeclField GhcRn -> RnM (LConDeclField DocNameI) diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index 657da7ae..399e5d0d 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -134,7 +134,7 @@ sugarTuples typ = sugarOperators :: HsType GhcRn -> HsType GhcRn sugarOperators (HsAppTy _ (L _ (HsAppTy _ (L _ (HsTyVar _ _ (L l name))) la)) lb) | isSymOcc $ getOccName name' = mkHsOpTy la (L l name) lb - | unrestrictedFunTyConName == name' = HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) la lb + | unrestrictedFunTyConName == name' = HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) la lb where name' = getName name sugarOperators typ = typ @@ -311,7 +311,7 @@ renameType t@(HsTyLit _ _) = pure t renameType (HsWildCardTy wc) = pure (HsWildCardTy wc) renameHsArrow :: HsArrow GhcRn -> Rename (IdP GhcRn) (HsArrow GhcRn) -renameHsArrow (HsExplicitMult u a p) = HsExplicitMult u a <$> renameLType p +renameHsArrow (HsExplicitMult pct p arr) = (\p' -> HsExplicitMult pct p' arr) <$> renameLType p renameHsArrow mult = pure mult -- cgit v1.2.3 From f7059f84687a6aac37405c428a97190662de1dac Mon Sep 17 00:00:00 2001 From: Sylvain Henry Date: Mon, 28 Jun 2021 19:21:17 +0200 Subject: Fix mkParserOpts (#1411) --- haddock-api/src/Haddock/Backends/Hoogle.hs | 1 - haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 8 ++++---- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index dfb167a3..29c64a2d 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -31,7 +31,6 @@ import GHC import GHC.Driver.Ppr import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic -import GHC.Parser.Annotation (IsUnicodeSyntax(..)) import GHC.Unit.State import Data.Char diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 49e2c66f..4e9099d8 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -13,7 +13,8 @@ import qualified Data.ByteString as BS import GHC.Platform import GHC.Types.SourceText import GHC.Driver.Session -import GHC.Utils.Error ( mkPlainMsgEnvelope, pprLocMsgEnvelope ) +import GHC.Driver.Config.Diagnostic +import GHC.Utils.Error ( pprLocMsgEnvelope ) import GHC.Data.FastString ( mkFastString ) import GHC.Parser.Errors.Ppr () import qualified GHC.Types.Error as E @@ -51,9 +52,8 @@ parse dflags fpath bs = case unP (go False []) initState of buf = stringBufferFromByteString bs start = mkRealSrcLoc (mkFastString fpath) 1 1 arch_os = platformArchOS (targetPlatform dflags) - pflags = mkParserOpts (warningFlags dflags) - (extensionFlags dflags) - (mkPlainMsgEnvelope dflags) + pflags = mkParserOpts (extensionFlags dflags) + (initDiagOpts dflags) (supportedLanguagesAndExtensions arch_os) (safeImportsOn dflags) False -- lex Haddocks as comment tokens -- cgit v1.2.3 From c3df9283872dbba1ac8c1ffd1b7e7ef4a54dee7b Mon Sep 17 00:00:00 2001 From: Alfredo Di Napoli Date: Wed, 30 Jun 2021 15:13:08 +0200 Subject: Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 4e9099d8..3929c286 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -20,7 +20,7 @@ import GHC.Parser.Errors.Ppr () import qualified GHC.Types.Error as E import GHC.Parser.Lexer as Lexer ( P(..), ParseResult(..), PState(..), Token(..) - , initParserState, lexer, mkParserOpts, getErrorMessages) + , initParserState, lexer, mkParserOpts, getPsErrorMessages) import GHC.Data.Bag ( bagToList ) import GHC.Utils.Outputable ( text, ($$) ) import GHC.Utils.Panic ( panic ) @@ -43,7 +43,7 @@ parse parse dflags fpath bs = case unP (go False []) initState of POk _ toks -> reverse toks PFailed pst -> - let err:_ = bagToList (E.getMessages $ getErrorMessages pst) in + let err:_ = bagToList (E.getMessages $ getPsErrorMessages pst) in panic $ showSDoc dflags $ text "Hyperlinker parse error:" $$ pprLocMsgEnvelope err where -- cgit v1.2.3 From 1b63771dee5a7fac0696505d0b335908bd12835d Mon Sep 17 00:00:00 2001 From: Marcin Szamotulski Date: Mon, 16 Aug 2021 08:46:03 +0200 Subject: coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". --- doc/index.rst | 1 + doc/intro.rst | 1 + doc/invoking.rst | 7 + doc/multi-components.rst | 48 + haddock-api/haddock-api.cabal | 6 + haddock-api/resources/html/haddock-bundle.min.js | 2 +- haddock-api/resources/html/js-src/init.ts | 7 +- haddock-api/resources/html/package-lock.json | 6338 +++++++++++++++++++++- haddock-api/src/Haddock.hs | 81 +- haddock-api/src/Haddock/Backends/Xhtml.hs | 137 +- haddock-api/src/Haddock/Backends/Xhtml/Themes.hs | 7 +- haddock-api/src/Haddock/Backends/Xhtml/Types.hs | 11 + haddock-api/src/Haddock/Options.hs | 7 + haddock-api/src/Haddock/Utils/Json.hs | 378 +- haddock-api/src/Haddock/Utils/Json/Parser.hs | 102 + haddock-api/src/Haddock/Utils/Json/Types.hs | 42 + haddock.cabal | 2 + 17 files changed, 7059 insertions(+), 118 deletions(-) create mode 100644 doc/multi-components.rst create mode 100644 haddock-api/src/Haddock/Utils/Json/Parser.hs create mode 100644 haddock-api/src/Haddock/Utils/Json/Types.hs diff --git a/doc/index.rst b/doc/index.rst index dc30c45f..0d1b8b48 100644 --- a/doc/index.rst +++ b/doc/index.rst @@ -12,6 +12,7 @@ Contents: intro invoking markup + multi-components Indices and tables diff --git a/doc/intro.rst b/doc/intro.rst index a3497426..fc1269f9 100644 --- a/doc/intro.rst +++ b/doc/intro.rst @@ -125,6 +125,7 @@ please contact us. - Luke Plant - Malcolm Wallace - Manuel Chakravarty +- Marcin Szamotulski - Mark Lentczner - Mark Shields - Mateusz Kowalczyk diff --git a/doc/invoking.rst b/doc/invoking.rst index 4e4b8764..68e01d70 100644 --- a/doc/invoking.rst +++ b/doc/invoking.rst @@ -223,6 +223,13 @@ The following options are available: Reserved for future use (output documentation in DocBook XML format). +.. option:: --base-url= + + Base url for static assets (eg. css, javascript, json files etc.). + When present, static assets are not copied. This option is useful + when creating documentation for multiple packages, it allows to have + a single copy of static assets served from the given url. + .. option:: --source-base= --source-module= --source-entity= diff --git a/doc/multi-components.rst b/doc/multi-components.rst new file mode 100644 index 00000000..9f52cad3 --- /dev/null +++ b/doc/multi-components.rst @@ -0,0 +1,48 @@ +Haddocks of multiple components +=============================== + +Haddock supports building documentation of multiple components. First, one +needs to build haddocks of all components which can be done with: + +.. code-block:: none + + cabal haddock --haddock-html \ + --haddock-quickjump \ + --haddock-option="--use-index=../doc-index.html" \ + --haddock-option="--use-contents=../index.html" \ + --haddock-option="--base-url=.." \ + all + +The new ``--base-url`` option will allow to access the static files from the +main directory (in this example its the relative ``./..`` directory). It will +also prevent ``haddock`` from copying its static files to each of the +documentation folders, we're only need a single copy of them where the +``--base-url`` option points to. + +The second step requires to copy all the haddocks to a common directory, let's +say ``./docs``, this will depend on your project and it might look like: + +.. code-block:: none + + cp -r dist-newstyle/build/x86_64-linux/ghc-9.0.1/package-a-0.1.0.0/doc/html/package-a/ docs + cp -r dist-newstyle/build/x86_64-linux/ghc-9.0.1/package-b-0.1.0.0/doc/html/package-b/ docs + +Note that you can also include documentation of other packages in this way, +e.g. ``base``, but you need to know where it is hidden on your hard-drive. + +To build html and js (``quickjump``) indexes one can now invoke ``haddock`` with: + +.. code-block:: none + + haddock \ + -o docs \ + --quickjump --gen-index --gen-contents \ + --read-interface=package-a,docs/package-a/package-a.haddock \ + --read-interface=package-b,docs/package-b/package-b.haddock + +Note: the ``PATH`` in ``--read-interface=PATH,...`` must be a relative url of +a package it points to (relative to the ``docs`` directory). + +There's an example project which shows how to do that posted `here +`_, which haddocks are served on +`github-pages `_. diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index feecf40a..cd02bf25 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -48,6 +48,7 @@ library , ghc-paths ^>= 0.1.0.9 , haddock-library ^>= 1.9.0 , xhtml ^>= 3000.2.2 + , parsec ^>= 3.1.13.0 -- Versions for the dependencies below are transitively pinned by -- the non-reinstallable `ghc` package and hence need no version @@ -93,6 +94,8 @@ library Haddock.Parser Haddock.Utils Haddock.Utils.Json + Haddock.Utils.Json.Types + Haddock.Utils.Json.Parser Haddock.Backends.Xhtml Haddock.Backends.Xhtml.Decl Haddock.Backends.Xhtml.DocMarkup @@ -169,6 +172,8 @@ test-suite spec Haddock.Types Haddock.Utils Haddock.Utils.Json + Haddock.Utils.Json.Types + Haddock.Utils.Json.Parser Haddock.Version Paths_haddock_api Haddock.Backends.Hyperlinker.ParserSpec @@ -180,6 +185,7 @@ test-suite spec , haddock-library ^>= 1.9.0 , xhtml ^>= 3000.2.2 , hspec >= 2.4.4 && < 2.8 + , parsec ^>= 3.1.13.0 , QuickCheck >= 2.11 && ^>= 2.14 -- Versions for the dependencies below are transitively pinned by diff --git a/haddock-api/resources/html/haddock-bundle.min.js b/haddock-api/resources/html/haddock-bundle.min.js index 45adda98..188ab76a 100644 --- a/haddock-api/resources/html/haddock-bundle.min.js +++ b/haddock-api/resources/html/haddock-bundle.min.js @@ -1,2 +1,2 @@ -!function i(s,a,l){function c(t,e){if(!a[t]){if(!s[t]){var n="function"==typeof require&&require;if(!e&&n)return n(t,!0);if(u)return u(t,!0);var o=new Error("Cannot find module '"+t+"'");throw o.code="MODULE_NOT_FOUND",o}var r=a[t]={exports:{}};s[t][0].call(r.exports,function(e){return c(s[t][1][e]||e)},r,r.exports,i,s,a,l)}return a[t].exports}for(var u="function"==typeof require&&require,e=0;e element with id '"+e+"'");return t}function x(){return u.defaultInstanceState==i.Open}function w(e){for(var t=S(e.target.id),n=t.element.open,o=0,r=t.toggles;owindow.innerHeight?this.searchResults.scrollTop+=e.bottom-window.innerHeight+80:e.topn)return u(e,this.pattern,o);var r=this.options,i=r.location,s=r.distance,a=r.threshold,l=r.findAllMatches,c=r.minMatchCharLength;return d(e,this.pattern,this.patternAlphabet,{location:i,distance:s,threshold:a,findAllMatches:l,minMatchCharLength:c})}}]),y}();e.exports=r},function(e,t,n){"use strict";var u=n(0);e.exports=function(e,t){return function e(t,n,o){if(n){var r=n.indexOf("."),i=n,s=null;-1!==r&&(i=n.slice(0,r),s=n.slice(r+1));var a=t[i];if(null!=a)if(s||"string"!=typeof a&&"number"!=typeof a)if(u(a))for(var l=0,c=a.length;l 0 and <= 1");p=p.name}else a[p]={weight:1};this._analyze({key:p,value:this.options.getFn(u,p),record:u,index:l},{resultMap:o,results:r,tokenSearchers:e,fullSearcher:t})}return{weights:a,results:r}}},{key:"_analyze",value:function(e,t){var n=e.key,o=e.arrayIndex,r=void 0===o?-1:o,i=e.value,s=e.record,a=e.index,l=t.tokenSearchers,c=void 0===l?[]:l,u=t.fullSearcher,d=void 0===u?[]:u,h=t.resultMap,p=void 0===h?{}:h,f=t.results,v=void 0===f?[]:f;if(null!=i){var g=!1,m=-1,y=0;if("string"==typeof i){this._log("\nKey: "+(""===n?"-":n));var _=d.search(i);if(this._log('Full text: "'+i+'", score: '+_.score),this.options.tokenize){for(var b=i.split(this.options.tokenSeparator),k=[],S=0;S=c.length;if(this._log("\nCheck Matches: "+T),(g||_.isMatch)&&T){var N=p[a];N?N.output.push({key:n,arrayIndex:r,value:i,score:A,matchedIndices:_.matchedIndices}):(p[a]={item:s,output:[{key:n,arrayIndex:r,value:i,score:A,matchedIndices:_.matchedIndices}]},v.push(p[a]))}}else if(V(i))for(var P=0,j=i.length;P element with id '"+e+"'");return t}function x(){return u.defaultInstanceState==i.Open}function w(e){for(var t=S(e.target.id),n=t.element.open,o=0,r=t.toggles;owindow.innerHeight?this.searchResults.scrollTop+=e.bottom-window.innerHeight+80:e.topn)return u(e,this.pattern,o);var r=this.options,i=r.location,s=r.distance,a=r.threshold,l=r.findAllMatches,c=r.minMatchCharLength;return d(e,this.pattern,this.patternAlphabet,{location:i,distance:s,threshold:a,findAllMatches:l,minMatchCharLength:c})}}]),y}();e.exports=r},function(e,t,n){"use strict";var u=n(0);e.exports=function(e,t){return function e(t,n,o){if(n){var r=n.indexOf("."),i=n,s=null;-1!==r&&(i=n.slice(0,r),s=n.slice(r+1));var a=t[i];if(null!=a)if(s||"string"!=typeof a&&"number"!=typeof a)if(u(a))for(var l=0,c=a.length;l 0 and <= 1");p=p.name}else a[p]={weight:1};this._analyze({key:p,value:this.options.getFn(u,p),record:u,index:l},{resultMap:o,results:r,tokenSearchers:e,fullSearcher:t})}return{weights:a,results:r}}},{key:"_analyze",value:function(e,t){var n=e.key,o=e.arrayIndex,r=void 0===o?-1:o,i=e.value,s=e.record,a=e.index,l=t.tokenSearchers,c=void 0===l?[]:l,u=t.fullSearcher,d=void 0===u?[]:u,h=t.resultMap,p=void 0===h?{}:h,f=t.results,v=void 0===f?[]:f;if(null!=i){var g=!1,m=-1,y=0;if("string"==typeof i){this._log("\nKey: "+(""===n?"-":n));var _=d.search(i);if(this._log('Full text: "'+i+'", score: '+_.score),this.options.tokenize){for(var b=i.split(this.options.tokenSeparator),k=[],S=0;S=c.length;if(this._log("\nCheck Matches: "+T),(g||_.isMatch)&&T){var N=p[a];N?N.output.push({key:n,arrayIndex:r,value:i,score:A,matchedIndices:_.matchedIndices}):(p[a]={item:s,output:[{key:n,arrayIndex:r,value:i,score:A,matchedIndices:_.matchedIndices}]},v.push(p[a]))}}else if(V(i))for(var P=0,j=i.length;P void) { onDomReady(() => { document.body.classList.add('js-enabled'); styleMenu.init(); - quickJump.init(); detailsHelper.init(); + let head = document.getElementById('head'); + let baseURL = "."; + if (head !== null) { + baseURL = head.getAttribute('data-base-url') || '.'; + } + quickJump.init(baseURL); }); diff --git a/haddock-api/resources/html/package-lock.json b/haddock-api/resources/html/package-lock.json index f09bde68..67615fce 100644 --- a/haddock-api/resources/html/package-lock.json +++ b/haddock-api/resources/html/package-lock.json @@ -1,8 +1,6210 @@ { "name": "haddock-quick-jump", "version": "0.1.0", - "lockfileVersion": 1, + "lockfileVersion": 2, "requires": true, + "packages": { + "": { + "name": "haddock-quick-jump", + "version": "0.1.0", + "dependencies": { + "fuse.js": "^3.3.0", + "preact": "^8.3.1" + }, + "devDependencies": { + "browserify": "^14.5.0", + "gulp": "^4.0.0", + "gulp-sourcemaps": "^2.6.4", + "gulp-uglify": "^3.0.1", + "tsify": "^3.0.4", + "typescript": "^2.9.2", + "vinyl-buffer": "^1.0.1", + "vinyl-source-stream": "^2.0.0" + } + }, + "node_modules/@gulp-sourcemaps/identity-map": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/@gulp-sourcemaps/identity-map/-/identity-map-1.0.2.tgz", + "integrity": "sha512-ciiioYMLdo16ShmfHBXJBOFm3xPC4AuwO4xeRpFeHz7WK9PYsWCmigagG2XyzZpubK4a3qNKoUBDhbzHfa50LQ==", + "dev": true, + "dependencies": { + "acorn": "^5.0.3", + "css": "^2.2.1", + "normalize-path": "^2.1.1", + "source-map": "^0.6.0", + "through2": "^2.0.3" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/@gulp-sourcemaps/identity-map/node_modules/acorn": { + "version": "5.7.3", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-5.7.3.tgz", + "integrity": "sha512-T/zvzYRfbVojPWahDsE5evJdHb3oJoQfFbsrKM7w5Zcs++Tr257tia3BmMP8XYVjp1S9RZXQMh7gao96BlqZOw==", + "dev": true, + "bin": { + "acorn": "bin/acorn" + }, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/@gulp-sourcemaps/identity-map/node_modules/source-map": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/@gulp-sourcemaps/map-sources": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/@gulp-sourcemaps/map-sources/-/map-sources-1.0.0.tgz", + "integrity": "sha1-iQrnxdjId/bThIYCFazp1+yUW9o=", + "dev": true, + "dependencies": { + "normalize-path": "^2.0.1", + "through2": "^2.0.3" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/acorn": { + "version": "6.0.2", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-6.0.2.tgz", + "integrity": "sha512-GXmKIvbrN3TV7aVqAzVFaMW8F8wzVX7voEBRO3bDA64+EX37YSayggRJP5Xig6HYHBkWKpFg9W5gg6orklubhg==", + "dev": true, + "bin": { + "acorn": "bin/acorn" + }, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/acorn-dynamic-import": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/acorn-dynamic-import/-/acorn-dynamic-import-4.0.0.tgz", + "integrity": "sha512-d3OEjQV4ROpoflsnUA8HozoIR504TFxNivYEUi6uwz0IYhBkTDXGuWlNdMtybRt3nqVx/L6XqMt0FxkXuWKZhw==", + "dev": true + }, + "node_modules/acorn-node": { + "version": "1.6.1", + "resolved": "https://registry.npmjs.org/acorn-node/-/acorn-node-1.6.1.tgz", + "integrity": "sha512-B+fHENiJB8X0lNQQ/auxOqBC1xWig8RpxUAomCrlLJmNx1Z141WyRjwcEK4Ux7YRq3133H5Q6GYXch0rOa47NQ==", + "dev": true, + "dependencies": { + "acorn": "^6.0.1", + "acorn-dynamic-import": "^4.0.0", + "acorn-walk": "^6.0.1", + "xtend": "^4.0.1" + } + }, + "node_modules/acorn-walk": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/acorn-walk/-/acorn-walk-6.1.0.tgz", + "integrity": "sha512-ugTb7Lq7u4GfWSqqpwE0bGyoBZNMTok/zDBXxfEG0QM50jNlGhIWjRC1pPN7bvV1anhF+bs+/gNcRw+o55Evbg==", + "dev": true, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/ansi-colors": { + "version": "1.1.0", + "resolved": "http://registry.npmjs.org/ansi-colors/-/ansi-colors-1.1.0.tgz", + "integrity": "sha512-SFKX67auSNoVR38N3L+nvsPjOE0bybKTYbkf5tRvushrAPQ9V75huw0ZxBkKVeRU9kqH3d6HA4xTckbwZ4ixmA==", + "dev": true, + "dependencies": { + "ansi-wrap": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/ansi-gray": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/ansi-gray/-/ansi-gray-0.1.1.tgz", + "integrity": "sha1-KWLPVOyXksSFEKPetSRDaGHvclE=", + "dev": true, + "dependencies": { + "ansi-wrap": "0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/ansi-regex": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-2.1.1.tgz", + "integrity": "sha1-w7M6te42DYbg5ijwRorn7yfWVN8=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/ansi-wrap": { + "version": "0.1.0", + "resolved": "https://registry.npmjs.org/ansi-wrap/-/ansi-wrap-0.1.0.tgz", + "integrity": "sha1-qCJQ3bABXponyoLoLqYDu/pF768=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/any-promise": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/any-promise/-/any-promise-1.3.0.tgz", + "integrity": "sha1-q8av7tzqUugJzcA3au0845Y10X8=", + "dev": true + }, + "node_modules/anymatch": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/anymatch/-/anymatch-2.0.0.tgz", + "integrity": "sha512-5teOsQWABXHHBFP9y3skS5P3d/WfWXpv3FUpy+LorMrNYaT9pI4oLMQX7jzQ2KklNpGpWHzdCXTDT2Y3XGlZBw==", + "dev": true, + "dependencies": { + "micromatch": "^3.1.4", + "normalize-path": "^2.1.1" + } + }, + "node_modules/append-buffer": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/append-buffer/-/append-buffer-1.0.2.tgz", + "integrity": "sha1-2CIM9GYIFSXv6lBhTz3mUU36WPE=", + "dev": true, + "dependencies": { + "buffer-equal": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/archy": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/archy/-/archy-1.0.0.tgz", + "integrity": "sha1-+cjBN1fMHde8N5rHeyxipcKGjEA=", + "dev": true + }, + "node_modules/arr-diff": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/arr-diff/-/arr-diff-4.0.0.tgz", + "integrity": "sha1-1kYQdP6/7HHn4VI1dhoyml3HxSA=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/arr-filter": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/arr-filter/-/arr-filter-1.1.2.tgz", + "integrity": "sha1-Q/3d0JHo7xGqTEXZzcGOLf8XEe4=", + "dev": true, + "dependencies": { + "make-iterator": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/arr-flatten": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/arr-flatten/-/arr-flatten-1.1.0.tgz", + "integrity": "sha512-L3hKV5R/p5o81R7O02IGnwpDmkp6E982XhtbuwSe3O4qOtMMMtodicASA1Cny2U+aCXcNpml+m4dPsvsJ3jatg==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/arr-map": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/arr-map/-/arr-map-2.0.2.tgz", + "integrity": "sha1-Onc0X/wc814qkYJWAfnljy4kysQ=", + "dev": true, + "dependencies": { + "make-iterator": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/arr-union": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/arr-union/-/arr-union-3.1.0.tgz", + "integrity": "sha1-45sJrqne+Gao8gbiiK9jkZuuOcQ=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-each": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/array-each/-/array-each-1.0.1.tgz", + "integrity": "sha1-p5SvDAWrF1KEbudTofIRoFugxE8=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-filter": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/array-filter/-/array-filter-0.0.1.tgz", + "integrity": "sha1-fajPLiZijtcygDWB/SH2fKzS7uw=", + "dev": true + }, + "node_modules/array-initial": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/array-initial/-/array-initial-1.1.0.tgz", + "integrity": "sha1-L6dLJnOTccOUe9enrcc74zSz15U=", + "dev": true, + "dependencies": { + "array-slice": "^1.0.0", + "is-number": "^4.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-initial/node_modules/is-number": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/is-number/-/is-number-4.0.0.tgz", + "integrity": "sha512-rSklcAIlf1OmFdyAqbnWTLVelsQ58uvZ66S/ZyawjWqIviTWCjg2PzVGw8WUA+nNuPTqb4wgA+NszrJ+08LlgQ==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-last": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/array-last/-/array-last-1.3.0.tgz", + "integrity": "sha512-eOCut5rXlI6aCOS7Z7kCplKRKyiFQ6dHFBem4PwlwKeNFk2/XxTrhRh5T9PyaEWGy/NHTZWbY+nsZlNFJu9rYg==", + "dev": true, + "dependencies": { + "is-number": "^4.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-last/node_modules/is-number": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/is-number/-/is-number-4.0.0.tgz", + "integrity": "sha512-rSklcAIlf1OmFdyAqbnWTLVelsQ58uvZ66S/ZyawjWqIviTWCjg2PzVGw8WUA+nNuPTqb4wgA+NszrJ+08LlgQ==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-map": { + "version": "0.0.0", + "resolved": "https://registry.npmjs.org/array-map/-/array-map-0.0.0.tgz", + "integrity": "sha1-iKK6tz0c97zVwbEYoAP2b2ZfpmI=", + "dev": true + }, + "node_modules/array-reduce": { + "version": "0.0.0", + "resolved": "https://registry.npmjs.org/array-reduce/-/array-reduce-0.0.0.tgz", + "integrity": "sha1-FziZ0//Rx9k4PkR5Ul2+J4yrXys=", + "dev": true + }, + "node_modules/array-slice": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/array-slice/-/array-slice-1.1.0.tgz", + "integrity": "sha512-B1qMD3RBP7O8o0H2KbrXDyB0IccejMF15+87Lvlor12ONPRHP6gTjXMNkt/d3ZuOGbAe66hFmaCfECI24Ufp6w==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-sort": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/array-sort/-/array-sort-1.0.0.tgz", + "integrity": "sha512-ihLeJkonmdiAsD7vpgN3CRcx2J2S0TiYW+IS/5zHBI7mKUq3ySvBdzzBfD236ubDBQFiiyG3SWCPc+msQ9KoYg==", + "dev": true, + "dependencies": { + "default-compare": "^1.0.0", + "get-value": "^2.0.6", + "kind-of": "^5.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-sort/node_modules/kind-of": { + "version": "5.1.0", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-5.1.0.tgz", + "integrity": "sha512-NGEErnH6F2vUuXDh+OlbcKW7/wOcfdRHaZ7VWtqCztfHri/++YKmP51OdWeGPuqCOba6kk2OTe5d02VmTB80Pw==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/array-unique": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/array-unique/-/array-unique-0.3.2.tgz", + "integrity": "sha1-qJS3XUvE9s1nnvMkSp/Y9Gri1Cg=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/asn1.js": { + "version": "4.10.1", + "resolved": "https://registry.npmjs.org/asn1.js/-/asn1.js-4.10.1.tgz", + "integrity": "sha512-p32cOF5q0Zqs9uBiONKYLm6BClCoBCM5O9JfeUSlnQLBTxYdTK+pW+nXflm8UkKd2UYlEbYz5qEi0JuZR9ckSw==", + "dev": true, + "dependencies": { + "bn.js": "^4.0.0", + "inherits": "^2.0.1", + "minimalistic-assert": "^1.0.0" + } + }, + "node_modules/assert": { + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/assert/-/assert-1.4.1.tgz", + "integrity": "sha1-mZEtWRg2tab1s0XA8H7vwI/GXZE=", + "dev": true, + "dependencies": { + "util": "0.10.3" + } + }, + "node_modules/assert/node_modules/inherits": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.1.tgz", + "integrity": "sha1-sX0I0ya0Qj5Wjv9xn5GwscvfafE=", + "dev": true + }, + "node_modules/assert/node_modules/util": { + "version": "0.10.3", + "resolved": "https://registry.npmjs.org/util/-/util-0.10.3.tgz", + "integrity": "sha1-evsa/lCAUkZInj23/g7TeTNqwPk=", + "dev": true, + "dependencies": { + "inherits": "2.0.1" + } + }, + "node_modules/assign-symbols": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/assign-symbols/-/assign-symbols-1.0.0.tgz", + "integrity": "sha1-WWZ/QfrdTyDMvCu5a41Pf3jsA2c=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/async-done": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/async-done/-/async-done-1.3.1.tgz", + "integrity": "sha512-R1BaUeJ4PMoLNJuk+0tLJgjmEqVsdN118+Z8O+alhnQDQgy0kmD5Mqi0DNEmMx2LM0Ed5yekKu+ZXYvIHceicg==", + "dev": true, + "dependencies": { + "end-of-stream": "^1.1.0", + "once": "^1.3.2", + "process-nextick-args": "^1.0.7", + "stream-exhaust": "^1.0.1" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/async-each": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/async-each/-/async-each-1.0.1.tgz", + "integrity": "sha1-GdOGodntxufByF04iu28xW0zYC0=", + "dev": true + }, + "node_modules/async-settle": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/async-settle/-/async-settle-1.0.0.tgz", + "integrity": "sha1-HQqRS7Aldb7IqPOnTlCA9yssDGs=", + "dev": true, + "dependencies": { + "async-done": "^1.2.2" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/atob": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/atob/-/atob-2.1.2.tgz", + "integrity": "sha512-Wm6ukoaOGJi/73p/cl2GvLjTI5JM1k/O14isD73YML8StrH/7/lRFgmg8nICZgD3bZZvjwCGxtMOD3wWNAu8cg==", + "dev": true, + "bin": { + "atob": "bin/atob.js" + }, + "engines": { + "node": ">= 4.5.0" + } + }, + "node_modules/bach": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/bach/-/bach-1.2.0.tgz", + "integrity": "sha1-Szzpa/JxNPeaG0FKUcFONMO9mIA=", + "dev": true, + "dependencies": { + "arr-filter": "^1.1.1", + "arr-flatten": "^1.0.1", + "arr-map": "^2.0.0", + "array-each": "^1.0.0", + "array-initial": "^1.0.0", + "array-last": "^1.1.1", + "async-done": "^1.2.2", + "async-settle": "^1.0.0", + "now-and-later": "^2.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/balanced-match": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.0.tgz", + "integrity": "sha1-ibTRmasr7kneFk6gK4nORi1xt2c=", + "dev": true + }, + "node_modules/base": { + "version": "0.11.2", + "resolved": "https://registry.npmjs.org/base/-/base-0.11.2.tgz", + "integrity": "sha512-5T6P4xPgpp0YDFvSWwEZ4NoE3aM4QBQXDzmVbraCkFj8zHM+mba8SyqB5DbZWyR7mYHo6Y7BdQo3MoA4m0TeQg==", + "dev": true, + "dependencies": { + "cache-base": "^1.0.1", + "class-utils": "^0.3.5", + "component-emitter": "^1.2.1", + "define-property": "^1.0.0", + "isobject": "^3.0.1", + "mixin-deep": "^1.2.0", + "pascalcase": "^0.1.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/base/node_modules/define-property": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-1.0.0.tgz", + "integrity": "sha1-dp66rz9KY6rTr56NMEybvnm/sOY=", + "dev": true, + "dependencies": { + "is-descriptor": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/base/node_modules/is-accessor-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-accessor-descriptor/-/is-accessor-descriptor-1.0.0.tgz", + "integrity": "sha512-m5hnHTkcVsPfqx3AKlyttIPb7J+XykHvJP2B9bZDjlhLIoEq4XoK64Vg7boZlVWYK6LUY94dYPEE7Lh0ZkZKcQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/base/node_modules/is-data-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-data-descriptor/-/is-data-descriptor-1.0.0.tgz", + "integrity": "sha512-jbRXy1FmtAoCjQkVmIVYwuuqDFUbaOeDjmed1tOGPrsMhtJA4rD9tkgA0F1qJ3gRFRXcHYVkdeaP50Q5rE/jLQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/base/node_modules/is-descriptor": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-descriptor/-/is-descriptor-1.0.2.tgz", + "integrity": "sha512-2eis5WqQGV7peooDyLmNEPUrps9+SXX5c9pL3xEB+4e9HnGuDa7mB7kHxHw4CbqS9k1T2hOH3miL8n8WtiYVtg==", + "dev": true, + "dependencies": { + "is-accessor-descriptor": "^1.0.0", + "is-data-descriptor": "^1.0.0", + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/base64-js": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/base64-js/-/base64-js-1.3.0.tgz", + "integrity": "sha512-ccav/yGvoa80BQDljCxsmmQ3Xvx60/UpBIij5QN21W3wBi/hhIC9OoO+KLpu9IJTS9j4DRVJ3aDDF9cMSoa2lw==", + "dev": true + }, + "node_modules/binary-extensions": { + "version": "1.12.0", + "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-1.12.0.tgz", + "integrity": "sha512-DYWGk01lDcxeS/K9IHPGWfT8PsJmbXRtRd2Sx72Tnb8pcYZQFF1oSDb8hJtS1vhp212q1Rzi5dUf9+nq0o9UIg==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/bl": { + "version": "1.2.2", + "resolved": "http://registry.npmjs.org/bl/-/bl-1.2.2.tgz", + "integrity": "sha512-e8tQYnZodmebYDWGH7KMRvtzKXaJHx3BbilrgZCfvyLUYdKpK1t5PSPmpkny/SgiTSCnjfLW7v5rlONXVFkQEA==", + "dev": true, + "dependencies": { + "readable-stream": "^2.3.5", + "safe-buffer": "^5.1.1" + } + }, + "node_modules/bn.js": { + "version": "4.11.8", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.11.8.tgz", + "integrity": "sha512-ItfYfPLkWHUjckQCk8xC+LwxgK8NYcXywGigJgSwOP8Y2iyWT4f2vsZnoOXTTbo+o5yXmIUJ4gn5538SO5S3gA==", + "dev": true + }, + "node_modules/brace-expansion": { + "version": "1.1.8", + "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.8.tgz", + "integrity": "sha1-wHshHHyVLsH479Uad+8NHTmQopI=", + "dev": true, + "dependencies": { + "balanced-match": "^1.0.0", + "concat-map": "0.0.1" + } + }, + "node_modules/braces": { + "version": "2.3.2", + "resolved": "https://registry.npmjs.org/braces/-/braces-2.3.2.tgz", + "integrity": "sha512-aNdbnj9P8PjdXU4ybaWLK2IF3jc/EoDYbC7AazW6to3TRsfXxscC9UXOB5iDiEQrkyIbWp2SLQda4+QAa7nc3w==", + "dev": true, + "dependencies": { + "arr-flatten": "^1.1.0", + "array-unique": "^0.3.2", + "extend-shallow": "^2.0.1", + "fill-range": "^4.0.0", + "isobject": "^3.0.1", + "repeat-element": "^1.1.2", + "snapdragon": "^0.8.1", + "snapdragon-node": "^2.0.1", + "split-string": "^3.0.2", + "to-regex": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/braces/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/brorand": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/brorand/-/brorand-1.1.0.tgz", + "integrity": "sha1-EsJe/kCkXjwyPrhnWgoM5XsiNx8=", + "dev": true + }, + "node_modules/browser-pack": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/browser-pack/-/browser-pack-6.1.0.tgz", + "integrity": "sha512-erYug8XoqzU3IfcU8fUgyHqyOXqIE4tUTTQ+7mqUjQlvnXkOO6OlT9c/ZoJVHYoAaqGxr09CN53G7XIsO4KtWA==", + "dev": true, + "dependencies": { + "combine-source-map": "~0.8.0", + "defined": "^1.0.0", + "JSONStream": "^1.0.3", + "safe-buffer": "^5.1.1", + "through2": "^2.0.0", + "umd": "^3.0.0" + }, + "bin": { + "browser-pack": "bin/cmd.js" + } + }, + "node_modules/browser-resolve": { + "version": "1.11.3", + "resolved": "https://registry.npmjs.org/browser-resolve/-/browser-resolve-1.11.3.tgz", + "integrity": "sha512-exDi1BYWB/6raKHmDTCicQfTkqwN5fioMFV4j8BsfMU4R2DK/QfZfK7kOVkmWCNANf0snkBzqGqAJBao9gZMdQ==", + "dev": true, + "dependencies": { + "resolve": "1.1.7" + } + }, + "node_modules/browser-resolve/node_modules/resolve": { + "version": "1.1.7", + "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.1.7.tgz", + "integrity": "sha1-IDEU2CrSxe2ejgQRs5ModeiJ6Xs=", + "dev": true + }, + "node_modules/browserify": { + "version": "14.5.0", + "resolved": "https://registry.npmjs.org/browserify/-/browserify-14.5.0.tgz", + "integrity": "sha512-gKfOsNQv/toWz+60nSPfYzuwSEdzvV2WdxrVPUbPD/qui44rAkB3t3muNtmmGYHqrG56FGwX9SUEQmzNLAeS7g==", + "dev": true, + "dependencies": { + "assert": "^1.4.0", + "browser-pack": "^6.0.1", + "browser-resolve": "^1.11.0", + "browserify-zlib": "~0.2.0", + "buffer": "^5.0.2", + "cached-path-relative": "^1.0.0", + "concat-stream": "~1.5.1", + "console-browserify": "^1.1.0", + "constants-browserify": "~1.0.0", + "crypto-browserify": "^3.0.0", + "defined": "^1.0.0", + "deps-sort": "^2.0.0", + "domain-browser": "~1.1.0", + "duplexer2": "~0.1.2", + "events": "~1.1.0", + "glob": "^7.1.0", + "has": "^1.0.0", + "htmlescape": "^1.1.0", + "https-browserify": "^1.0.0", + "inherits": "~2.0.1", + "insert-module-globals": "^7.0.0", + "JSONStream": "^1.0.3", + "labeled-stream-splicer": "^2.0.0", + "module-deps": "^4.0.8", + "os-browserify": "~0.3.0", + "parents": "^1.0.1", + "path-browserify": "~0.0.0", + "process": "~0.11.0", + "punycode": "^1.3.2", + "querystring-es3": "~0.2.0", + "read-only-stream": "^2.0.0", + "readable-stream": "^2.0.2", + "resolve": "^1.1.4", + "shasum": "^1.0.0", + "shell-quote": "^1.6.1", + "stream-browserify": "^2.0.0", + "stream-http": "^2.0.0", + "string_decoder": "~1.0.0", + "subarg": "^1.0.0", + "syntax-error": "^1.1.1", + "through2": "^2.0.0", + "timers-browserify": "^1.0.1", + "tty-browserify": "~0.0.0", + "url": "~0.11.0", + "util": "~0.10.1", + "vm-browserify": "~0.0.1", + "xtend": "^4.0.0" + }, + "bin": { + "browserify": "bin/cmd.js" + } + }, + "node_modules/browserify-aes": { + "version": "1.2.0", + "resolved": "http://registry.npmjs.org/browserify-aes/-/browserify-aes-1.2.0.tgz", + "integrity": "sha512-+7CHXqGuspUn/Sl5aO7Ea0xWGAtETPXNSAjHo48JfLdPWcMng33Xe4znFvQweqc/uzk5zSOI3H52CYnjCfb5hA==", + "dev": true, + "dependencies": { + "buffer-xor": "^1.0.3", + "cipher-base": "^1.0.0", + "create-hash": "^1.1.0", + "evp_bytestokey": "^1.0.3", + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + } + }, + "node_modules/browserify-cipher": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/browserify-cipher/-/browserify-cipher-1.0.1.tgz", + "integrity": "sha512-sPhkz0ARKbf4rRQt2hTpAHqn47X3llLkUGn+xEJzLjwY8LRs2p0v7ljvI5EyoRO/mexrNunNECisZs+gw2zz1w==", + "dev": true, + "dependencies": { + "browserify-aes": "^1.0.4", + "browserify-des": "^1.0.0", + "evp_bytestokey": "^1.0.0" + } + }, + "node_modules/browserify-des": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/browserify-des/-/browserify-des-1.0.2.tgz", + "integrity": "sha512-BioO1xf3hFwz4kc6iBhI3ieDFompMhrMlnDFC4/0/vd5MokpuAc3R+LYbwTA9A5Yc9pq9UYPqffKpW2ObuwX5A==", + "dev": true, + "dependencies": { + "cipher-base": "^1.0.1", + "des.js": "^1.0.0", + "inherits": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/browserify-des/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/browserify-rsa": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/browserify-rsa/-/browserify-rsa-4.0.1.tgz", + "integrity": "sha1-IeCr+vbyApzy+vsTNWenAdQTVSQ=", + "dev": true, + "dependencies": { + "bn.js": "^4.1.0", + "randombytes": "^2.0.1" + } + }, + "node_modules/browserify-sign": { + "version": "4.0.4", + "resolved": "https://registry.npmjs.org/browserify-sign/-/browserify-sign-4.0.4.tgz", + "integrity": "sha1-qk62jl17ZYuqa/alfmMMvXqT0pg=", + "dev": true, + "dependencies": { + "bn.js": "^4.1.1", + "browserify-rsa": "^4.0.0", + "create-hash": "^1.1.0", + "create-hmac": "^1.1.2", + "elliptic": "^6.0.0", + "inherits": "^2.0.1", + "parse-asn1": "^5.0.0" + } + }, + "node_modules/browserify-zlib": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/browserify-zlib/-/browserify-zlib-0.2.0.tgz", + "integrity": "sha512-Z942RysHXmJrhqk88FmKBVq/v5tqmSkDz7p54G/MGyjMnCFFnC79XWNbg+Vta8W6Wb2qtSZTSxIGkJrRpCFEiA==", + "dev": true, + "dependencies": { + "pako": "~1.0.5" + } + }, + "node_modules/buffer": { + "version": "5.2.1", + "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.2.1.tgz", + "integrity": "sha512-c+Ko0loDaFfuPWiL02ls9Xd3GO3cPVmUobQ6t3rXNUk304u6hGq+8N/kFi+QEIKhzK3uwolVhLzszmfLmMLnqg==", + "dev": true, + "dependencies": { + "base64-js": "^1.0.2", + "ieee754": "^1.1.4" + } + }, + "node_modules/buffer-equal": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/buffer-equal/-/buffer-equal-1.0.0.tgz", + "integrity": "sha1-WWFrSYME1Var1GaWayLu2j7KX74=", + "dev": true, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/buffer-from": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.1.tgz", + "integrity": "sha512-MQcXEUbCKtEo7bhqEs6560Hyd4XaovZlO/k9V3hjVUF/zwW7KBVdSK4gIt/bzwS9MbR5qob+F5jusZsb0YQK2A==", + "dev": true + }, + "node_modules/buffer-xor": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/buffer-xor/-/buffer-xor-1.0.3.tgz", + "integrity": "sha1-JuYe0UIvtw3ULm42cp7VHYVf6Nk=", + "dev": true + }, + "node_modules/builtin-modules": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/builtin-modules/-/builtin-modules-1.1.1.tgz", + "integrity": "sha1-Jw8HbFpywC9bZaR9+Uxf46J4iS8=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/builtin-status-codes": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/builtin-status-codes/-/builtin-status-codes-3.0.0.tgz", + "integrity": "sha1-hZgoeOIbmOHGZCXgPQF0eI9Wnug=", + "dev": true + }, + "node_modules/cache-base": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/cache-base/-/cache-base-1.0.1.tgz", + "integrity": "sha512-AKcdTnFSWATd5/GCPRxr2ChwIJ85CeyrEyjRHlKxQ56d4XJMGym0uAiKn0xbLOGOl3+yRpOTi484dVCEc5AUzQ==", + "dev": true, + "dependencies": { + "collection-visit": "^1.0.0", + "component-emitter": "^1.2.1", + "get-value": "^2.0.6", + "has-value": "^1.0.0", + "isobject": "^3.0.1", + "set-value": "^2.0.0", + "to-object-path": "^0.3.0", + "union-value": "^1.0.0", + "unset-value": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/cached-path-relative": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/cached-path-relative/-/cached-path-relative-1.0.1.tgz", + "integrity": "sha1-0JxLUoAKpMB44t2BqGmqyQ0uVOc=", + "dev": true + }, + "node_modules/camelcase": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/camelcase/-/camelcase-3.0.0.tgz", + "integrity": "sha1-MvxLn82vhF/N9+c7uXysImHwqwo=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/chokidar": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/chokidar/-/chokidar-2.0.4.tgz", + "integrity": "sha512-z9n7yt9rOvIJrMhvDtDictKrkFHeihkNl6uWMmZlmL6tJtX9Cs+87oK+teBx+JIgzvbX3yZHT3eF8vpbDxHJXQ==", + "dev": true, + "dependencies": { + "anymatch": "^2.0.0", + "async-each": "^1.0.0", + "braces": "^2.3.0", + "fsevents": "^1.2.2", + "glob-parent": "^3.1.0", + "inherits": "^2.0.1", + "is-binary-path": "^1.0.0", + "is-glob": "^4.0.0", + "lodash.debounce": "^4.0.8", + "normalize-path": "^2.1.1", + "path-is-absolute": "^1.0.0", + "readdirp": "^2.0.0", + "upath": "^1.0.5" + }, + "optionalDependencies": { + "fsevents": "^1.2.2" + } + }, + "node_modules/cipher-base": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/cipher-base/-/cipher-base-1.0.4.tgz", + "integrity": "sha512-Kkht5ye6ZGmwv40uUDZztayT2ThLQGfnj/T71N/XzeZeo3nf8foyW7zGTsPYkEya3m5f3cAypH+qe7YOrM1U2Q==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + } + }, + "node_modules/class-utils": { + "version": "0.3.6", + "resolved": "https://registry.npmjs.org/class-utils/-/class-utils-0.3.6.tgz", + "integrity": "sha512-qOhPa/Fj7s6TY8H8esGu5QNpMMQxz79h+urzrNYN6mn+9BnxlDGf5QZ+XeCDsxSjPqsSR56XOZOJmpeurnLMeg==", + "dev": true, + "dependencies": { + "arr-union": "^3.1.0", + "define-property": "^0.2.5", + "isobject": "^3.0.0", + "static-extend": "^0.1.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/class-utils/node_modules/define-property": { + "version": "0.2.5", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-0.2.5.tgz", + "integrity": "sha1-w1se+RjsPJkPmlvFe+BKrOxcgRY=", + "dev": true, + "dependencies": { + "is-descriptor": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/cliui": { + "version": "3.2.0", + "resolved": "https://registry.npmjs.org/cliui/-/cliui-3.2.0.tgz", + "integrity": "sha1-EgYBU3qRbSmUD5NNo7SNWFo5IT0=", + "dev": true, + "dependencies": { + "string-width": "^1.0.1", + "strip-ansi": "^3.0.1", + "wrap-ansi": "^2.0.0" + } + }, + "node_modules/clone-buffer": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/clone-buffer/-/clone-buffer-1.0.0.tgz", + "integrity": "sha1-4+JbIHrE5wGvch4staFnksrD3Fg=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/cloneable-readable": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/cloneable-readable/-/cloneable-readable-1.1.2.tgz", + "integrity": "sha512-Bq6+4t+lbM8vhTs/Bef5c5AdEMtapp/iFb6+s4/Hh9MVTt8OLKH7ZOOZSCT+Ys7hsHvqv0GuMPJ1lnQJVHvxpg==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "process-nextick-args": "^2.0.0", + "readable-stream": "^2.3.5" + } + }, + "node_modules/cloneable-readable/node_modules/process-nextick-args": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.0.tgz", + "integrity": "sha512-MtEC1TqN0EU5nephaJ4rAtThHtC86dNN9qCuEhtshvpVBkAW5ZO7BASN9REnF9eoXGcRub+pFuKEpOHE+HbEMw==", + "dev": true + }, + "node_modules/code-point-at": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/code-point-at/-/code-point-at-1.1.0.tgz", + "integrity": "sha1-DQcLTQQ6W+ozovGkDi7bPZpMz3c=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/collection-map": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/collection-map/-/collection-map-1.0.0.tgz", + "integrity": "sha1-rqDwb40mx4DCt1SUOFVEsiVa8Yw=", + "dev": true, + "dependencies": { + "arr-map": "^2.0.2", + "for-own": "^1.0.0", + "make-iterator": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/collection-visit": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/collection-visit/-/collection-visit-1.0.0.tgz", + "integrity": "sha1-S8A3PBZLwykbTTaMgpzxqApZ3KA=", + "dev": true, + "dependencies": { + "map-visit": "^1.0.0", + "object-visit": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/color-support": { + "version": "1.1.3", + "resolved": "https://registry.npmjs.org/color-support/-/color-support-1.1.3.tgz", + "integrity": "sha512-qiBjkpbMLO/HL68y+lh4q0/O1MZFj2RX6X/KmMa3+gJD3z+WwI1ZzDHysvqHGS3mP6mznPckpXmw1nI9cJjyRg==", + "dev": true, + "bin": { + "color-support": "bin.js" + } + }, + "node_modules/combine-source-map": { + "version": "0.8.0", + "resolved": "https://registry.npmjs.org/combine-source-map/-/combine-source-map-0.8.0.tgz", + "integrity": "sha1-pY0N8ELBhvz4IqjoAV9UUNLXmos=", + "dev": true, + "dependencies": { + "convert-source-map": "~1.1.0", + "inline-source-map": "~0.6.0", + "lodash.memoize": "~3.0.3", + "source-map": "~0.5.3" + } + }, + "node_modules/commander": { + "version": "2.17.1", + "resolved": "https://registry.npmjs.org/commander/-/commander-2.17.1.tgz", + "integrity": "sha512-wPMUt6FnH2yzG95SA6mzjQOEKUU3aLaDEmzs1ti+1E9h+CsrZghRlqEM/EJ4KscsQVG8uNN4uVreUeT8+drlgg==", + "dev": true + }, + "node_modules/component-emitter": { + "version": "1.2.1", + "resolved": "https://registry.npmjs.org/component-emitter/-/component-emitter-1.2.1.tgz", + "integrity": "sha1-E3kY1teCg/ffemt8WmPhQOaUJeY=", + "dev": true + }, + "node_modules/concat-map": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", + "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=", + "dev": true + }, + "node_modules/concat-stream": { + "version": "1.5.2", + "resolved": "https://registry.npmjs.org/concat-stream/-/concat-stream-1.5.2.tgz", + "integrity": "sha1-cIl4Yk2FavQaWnQd790mHadSwmY=", + "dev": true, + "engines": [ + "node >= 0.8" + ], + "dependencies": { + "inherits": "~2.0.1", + "readable-stream": "~2.0.0", + "typedarray": "~0.0.5" + } + }, + "node_modules/concat-stream/node_modules/readable-stream": { + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.0.6.tgz", + "integrity": "sha1-j5A0HmilPMySh4jaz80Rs265t44=", + "dev": true, + "dependencies": { + "core-util-is": "~1.0.0", + "inherits": "~2.0.1", + "isarray": "~1.0.0", + "process-nextick-args": "~1.0.6", + "string_decoder": "~0.10.x", + "util-deprecate": "~1.0.1" + } + }, + "node_modules/concat-stream/node_modules/string_decoder": { + "version": "0.10.31", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-0.10.31.tgz", + "integrity": "sha1-YuIDvEF2bGwoyfyEMB2rHFMQ+pQ=", + "dev": true + }, + "node_modules/console-browserify": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/console-browserify/-/console-browserify-1.1.0.tgz", + "integrity": "sha1-8CQcRXMKn8YyOyBtvzjtx0HQuxA=", + "dev": true, + "dependencies": { + "date-now": "^0.1.4" + } + }, + "node_modules/constants-browserify": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/constants-browserify/-/constants-browserify-1.0.0.tgz", + "integrity": "sha1-wguW2MYXdIqvHBYCF2DNJ/y4y3U=", + "dev": true + }, + "node_modules/convert-source-map": { + "version": "1.1.3", + "resolved": "https://registry.npmjs.org/convert-source-map/-/convert-source-map-1.1.3.tgz", + "integrity": "sha1-SCnId+n+SbMWHzvzZziI4gRpmGA=", + "dev": true + }, + "node_modules/copy-descriptor": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/copy-descriptor/-/copy-descriptor-0.1.1.tgz", + "integrity": "sha1-Z29us8OZl8LuGsOpJP1hJHSPV40=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/copy-props": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/copy-props/-/copy-props-2.0.4.tgz", + "integrity": "sha512-7cjuUME+p+S3HZlbllgsn2CDwS+5eCCX16qBgNC4jgSTf49qR1VKy/Zhl400m0IQXl/bPGEVqncgUUMjrr4s8A==", + "dev": true, + "dependencies": { + "each-props": "^1.3.0", + "is-plain-object": "^2.0.1" + } + }, + "node_modules/core-util-is": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.2.tgz", + "integrity": "sha1-tf1UIgqivFq1eqtxQMlAdUUDwac=", + "dev": true + }, + "node_modules/create-ecdh": { + "version": "4.0.3", + "resolved": "https://registry.npmjs.org/create-ecdh/-/create-ecdh-4.0.3.tgz", + "integrity": "sha512-GbEHQPMOswGpKXM9kCWVrremUcBmjteUaQ01T9rkKCPDXfUHX0IoP9LpHYo2NPFampa4e+/pFDc3jQdxrxQLaw==", + "dev": true, + "dependencies": { + "bn.js": "^4.1.0", + "elliptic": "^6.0.0" + } + }, + "node_modules/create-hash": { + "version": "1.2.0", + "resolved": "http://registry.npmjs.org/create-hash/-/create-hash-1.2.0.tgz", + "integrity": "sha512-z00bCGNHDG8mHAkP7CtT1qVu+bFQUPjYq/4Iv3C3kWjTFV10zIjfSoeqXo9Asws8gwSHDGj/hl2u4OGIjapeCg==", + "dev": true, + "dependencies": { + "cipher-base": "^1.0.1", + "inherits": "^2.0.1", + "md5.js": "^1.3.4", + "ripemd160": "^2.0.1", + "sha.js": "^2.4.0" + } + }, + "node_modules/create-hmac": { + "version": "1.1.7", + "resolved": "http://registry.npmjs.org/create-hmac/-/create-hmac-1.1.7.tgz", + "integrity": "sha512-MJG9liiZ+ogc4TzUwuvbER1JRdgvUFSB5+VR/g5h82fGaIRWMWddtKBHi7/sVhfjQZ6SehlyhvQYrcYkaUIpLg==", + "dev": true, + "dependencies": { + "cipher-base": "^1.0.3", + "create-hash": "^1.1.0", + "inherits": "^2.0.1", + "ripemd160": "^2.0.0", + "safe-buffer": "^5.0.1", + "sha.js": "^2.4.8" + } + }, + "node_modules/crypto-browserify": { + "version": "3.12.0", + "resolved": "https://registry.npmjs.org/crypto-browserify/-/crypto-browserify-3.12.0.tgz", + "integrity": "sha512-fz4spIh+znjO2VjL+IdhEpRJ3YN6sMzITSBijk6FK2UvTqruSQW+/cCZTSNsMiZNvUeq0CqurF+dAbyiGOY6Wg==", + "dev": true, + "dependencies": { + "browserify-cipher": "^1.0.0", + "browserify-sign": "^4.0.0", + "create-ecdh": "^4.0.0", + "create-hash": "^1.1.0", + "create-hmac": "^1.1.0", + "diffie-hellman": "^5.0.0", + "inherits": "^2.0.1", + "pbkdf2": "^3.0.3", + "public-encrypt": "^4.0.0", + "randombytes": "^2.0.0", + "randomfill": "^1.0.3" + }, + "engines": { + "node": "*" + } + }, + "node_modules/css": { + "version": "2.2.4", + "resolved": "https://registry.npmjs.org/css/-/css-2.2.4.tgz", + "integrity": "sha512-oUnjmWpy0niI3x/mPL8dVEI1l7MnG3+HHyRPHf+YFSbK+svOhXpmSOcDURUh2aOCgl2grzrOPt1nHLuCVFULLw==", + "dev": true, + "dependencies": { + "inherits": "^2.0.3", + "source-map": "^0.6.1", + "source-map-resolve": "^0.5.2", + "urix": "^0.1.0" + } + }, + "node_modules/css/node_modules/source-map": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/d": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/d/-/d-1.0.0.tgz", + "integrity": "sha1-dUu1v+VUUdpppYuU1F9MWwRi1Y8=", + "dev": true, + "dependencies": { + "es5-ext": "^0.10.9" + } + }, + "node_modules/date-now": { + "version": "0.1.4", + "resolved": "https://registry.npmjs.org/date-now/-/date-now-0.1.4.tgz", + "integrity": "sha1-6vQ5/U1ISK105cx9vvIAZyueNFs=", + "dev": true + }, + "node_modules/debug": { + "version": "2.6.9", + "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", + "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", + "dev": true, + "dependencies": { + "ms": "2.0.0" + } + }, + "node_modules/debug-fabulous": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/debug-fabulous/-/debug-fabulous-1.1.0.tgz", + "integrity": "sha512-GZqvGIgKNlUnHUPQhepnUZFIMoi3dgZKQBzKDeL2g7oJF9SNAji/AAu36dusFUas0O+pae74lNeoIPHqXWDkLg==", + "dev": true, + "dependencies": { + "debug": "3.X", + "memoizee": "0.4.X", + "object-assign": "4.X" + } + }, + "node_modules/debug-fabulous/node_modules/debug": { + "version": "3.2.6", + "resolved": "https://registry.npmjs.org/debug/-/debug-3.2.6.tgz", + "integrity": "sha512-mel+jf7nrtEl5Pn1Qx46zARXKDpBbvzezse7p7LqINmdoIk8PYP5SySaxEmYv6TZ0JyEKA1hsCId6DIhgITtWQ==", + "dev": true, + "dependencies": { + "ms": "^2.1.1" + } + }, + "node_modules/debug-fabulous/node_modules/ms": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.1.tgz", + "integrity": "sha512-tgp+dl5cGk28utYktBsrFqA7HKgrhgPsg6Z/EfhWI4gl1Hwq8B/GmY/0oXZ6nF8hDVesS/FpnYaD/kOWhYQvyg==", + "dev": true + }, + "node_modules/debug/node_modules/ms": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", + "integrity": "sha1-VgiurfwAvmwpAd9fmGF4jeDVl8g=", + "dev": true + }, + "node_modules/decamelize": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/decamelize/-/decamelize-1.2.0.tgz", + "integrity": "sha1-9lNNFRSCabIDUue+4m9QH5oZEpA=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/decode-uri-component": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/decode-uri-component/-/decode-uri-component-0.2.0.tgz", + "integrity": "sha1-6zkTMzRYd1y4TNGh+uBiEGu4dUU=", + "dev": true, + "engines": { + "node": ">=0.10" + } + }, + "node_modules/default-compare": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/default-compare/-/default-compare-1.0.0.tgz", + "integrity": "sha512-QWfXlM0EkAbqOCbD/6HjdwT19j7WCkMyiRhWilc4H9/5h/RzTF9gv5LYh1+CmDV5d1rki6KAWLtQale0xt20eQ==", + "dev": true, + "dependencies": { + "kind-of": "^5.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/default-compare/node_modules/kind-of": { + "version": "5.1.0", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-5.1.0.tgz", + "integrity": "sha512-NGEErnH6F2vUuXDh+OlbcKW7/wOcfdRHaZ7VWtqCztfHri/++YKmP51OdWeGPuqCOba6kk2OTe5d02VmTB80Pw==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/default-resolution": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/default-resolution/-/default-resolution-2.0.0.tgz", + "integrity": "sha1-vLgrqnKtebQmp2cy8aga1t8m1oQ=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/define-properties": { + "version": "1.1.3", + "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.3.tgz", + "integrity": "sha512-3MqfYKj2lLzdMSf8ZIZE/V+Zuy+BgD6f164e8K2w7dgnpKArBDerGYpM46IYYcjnkdPNMjPk9A6VFB8+3SKlXQ==", + "dev": true, + "dependencies": { + "object-keys": "^1.0.12" + }, + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/define-property": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-2.0.2.tgz", + "integrity": "sha512-jwK2UV4cnPpbcG7+VRARKTZPUWowwXA8bzH5NP6ud0oeAxyYPuGZUAC7hMugpCdz4BeSZl2Dl9k66CHJ/46ZYQ==", + "dev": true, + "dependencies": { + "is-descriptor": "^1.0.2", + "isobject": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/define-property/node_modules/is-accessor-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-accessor-descriptor/-/is-accessor-descriptor-1.0.0.tgz", + "integrity": "sha512-m5hnHTkcVsPfqx3AKlyttIPb7J+XykHvJP2B9bZDjlhLIoEq4XoK64Vg7boZlVWYK6LUY94dYPEE7Lh0ZkZKcQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/define-property/node_modules/is-data-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-data-descriptor/-/is-data-descriptor-1.0.0.tgz", + "integrity": "sha512-jbRXy1FmtAoCjQkVmIVYwuuqDFUbaOeDjmed1tOGPrsMhtJA4rD9tkgA0F1qJ3gRFRXcHYVkdeaP50Q5rE/jLQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/define-property/node_modules/is-descriptor": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-descriptor/-/is-descriptor-1.0.2.tgz", + "integrity": "sha512-2eis5WqQGV7peooDyLmNEPUrps9+SXX5c9pL3xEB+4e9HnGuDa7mB7kHxHw4CbqS9k1T2hOH3miL8n8WtiYVtg==", + "dev": true, + "dependencies": { + "is-accessor-descriptor": "^1.0.0", + "is-data-descriptor": "^1.0.0", + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/defined": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/defined/-/defined-1.0.0.tgz", + "integrity": "sha1-yY2bzvdWdBiOEQlpFRGZ45sfppM=", + "dev": true + }, + "node_modules/deps-sort": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/deps-sort/-/deps-sort-2.0.0.tgz", + "integrity": "sha1-CRckkC6EZYJg65EHSMzNGvbiH7U=", + "dev": true, + "dependencies": { + "JSONStream": "^1.0.3", + "shasum": "^1.0.0", + "subarg": "^1.0.0", + "through2": "^2.0.0" + }, + "bin": { + "deps-sort": "bin/cmd.js" + } + }, + "node_modules/des.js": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/des.js/-/des.js-1.0.0.tgz", + "integrity": "sha1-wHTS4qpqipoH29YfmhXCzYPsjsw=", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "minimalistic-assert": "^1.0.0" + } + }, + "node_modules/detect-file": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/detect-file/-/detect-file-1.0.0.tgz", + "integrity": "sha1-8NZtA2cqglyxtzvbP+YjEMjlUrc=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/detect-newline": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/detect-newline/-/detect-newline-2.1.0.tgz", + "integrity": "sha1-9B8cEL5LAOh7XxPaaAdZ8sW/0+I=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/detective": { + "version": "4.7.1", + "resolved": "https://registry.npmjs.org/detective/-/detective-4.7.1.tgz", + "integrity": "sha512-H6PmeeUcZloWtdt4DAkFyzFL94arpHr3NOwwmVILFiy+9Qd4JTxxXrzfyGk/lmct2qVGBwTSwSXagqu2BxmWig==", + "dev": true, + "dependencies": { + "acorn": "^5.2.1", + "defined": "^1.0.0" + } + }, + "node_modules/detective/node_modules/acorn": { + "version": "5.7.3", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-5.7.3.tgz", + "integrity": "sha512-T/zvzYRfbVojPWahDsE5evJdHb3oJoQfFbsrKM7w5Zcs++Tr257tia3BmMP8XYVjp1S9RZXQMh7gao96BlqZOw==", + "dev": true, + "bin": { + "acorn": "bin/acorn" + }, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/diffie-hellman": { + "version": "5.0.3", + "resolved": "http://registry.npmjs.org/diffie-hellman/-/diffie-hellman-5.0.3.tgz", + "integrity": "sha512-kqag/Nl+f3GwyK25fhUMYj81BUOrZ9IuJsjIcDE5icNM9FJHAVm3VcUDxdLPoQtTuUylWm6ZIknYJwwaPxsUzg==", + "dev": true, + "dependencies": { + "bn.js": "^4.1.0", + "miller-rabin": "^4.0.0", + "randombytes": "^2.0.0" + } + }, + "node_modules/domain-browser": { + "version": "1.1.7", + "resolved": "https://registry.npmjs.org/domain-browser/-/domain-browser-1.1.7.tgz", + "integrity": "sha1-hnqksJP6oF8d4IwG9NeyH9+GmLw=", + "dev": true, + "engines": { + "node": ">=0.4", + "npm": ">=1.2" + } + }, + "node_modules/duplexer2": { + "version": "0.1.4", + "resolved": "https://registry.npmjs.org/duplexer2/-/duplexer2-0.1.4.tgz", + "integrity": "sha1-ixLauHjA1p4+eJEFFmKjL8a93ME=", + "dev": true, + "dependencies": { + "readable-stream": "^2.0.2" + } + }, + "node_modules/duplexify": { + "version": "3.6.1", + "resolved": "https://registry.npmjs.org/duplexify/-/duplexify-3.6.1.tgz", + "integrity": "sha512-vM58DwdnKmty+FSPzT14K9JXb90H+j5emaR4KYbr2KTIz00WHGbWOe5ghQTx233ZCLZtrGDALzKwcjEtSt35mA==", + "dev": true, + "dependencies": { + "end-of-stream": "^1.0.0", + "inherits": "^2.0.1", + "readable-stream": "^2.0.0", + "stream-shift": "^1.0.0" + } + }, + "node_modules/each-props": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/each-props/-/each-props-1.3.2.tgz", + "integrity": "sha512-vV0Hem3zAGkJAyU7JSjixeU66rwdynTAa1vofCrSA5fEln+m67Az9CcnkVD776/fsN/UjIWmBDoNRS6t6G9RfA==", + "dev": true, + "dependencies": { + "is-plain-object": "^2.0.1", + "object.defaults": "^1.1.0" + } + }, + "node_modules/elliptic": { + "version": "6.4.1", + "resolved": "https://registry.npmjs.org/elliptic/-/elliptic-6.4.1.tgz", + "integrity": "sha512-BsXLz5sqX8OHcsh7CqBMztyXARmGQ3LWPtGjJi6DiJHq5C/qvi9P3OqgswKSDftbu8+IoI/QDTAm2fFnQ9SZSQ==", + "dev": true, + "dependencies": { + "bn.js": "^4.4.0", + "brorand": "^1.0.1", + "hash.js": "^1.0.0", + "hmac-drbg": "^1.0.0", + "inherits": "^2.0.1", + "minimalistic-assert": "^1.0.0", + "minimalistic-crypto-utils": "^1.0.0" + } + }, + "node_modules/end-of-stream": { + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/end-of-stream/-/end-of-stream-1.4.1.tgz", + "integrity": "sha512-1MkrZNvWTKCaigbn+W15elq2BB/L22nqrSY5DKlo3X6+vclJm8Bb5djXJBmEX6fS3+zCh/F4VBK5Z2KxJt4s2Q==", + "dev": true, + "dependencies": { + "once": "^1.4.0" + } + }, + "node_modules/end-of-stream/node_modules/once": { + "version": "1.4.0", + "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", + "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", + "dev": true, + "dependencies": { + "wrappy": "1" + } + }, + "node_modules/error-ex": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/error-ex/-/error-ex-1.3.1.tgz", + "integrity": "sha1-+FWobOYa3E6GIcPNoh56dhLDqNw=", + "dev": true, + "dependencies": { + "is-arrayish": "^0.2.1" + } + }, + "node_modules/es5-ext": { + "version": "0.10.30", + "resolved": "https://registry.npmjs.org/es5-ext/-/es5-ext-0.10.30.tgz", + "integrity": "sha1-cUGhaDZpfbq/qq7uQUlc4p9SyTk=", + "dev": true, + "dependencies": { + "es6-iterator": "2", + "es6-symbol": "~3.1" + } + }, + "node_modules/es6-iterator": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/es6-iterator/-/es6-iterator-2.0.1.tgz", + "integrity": "sha1-jjGcnwRTv1ddN0lAplWSDlnKVRI=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "^0.10.14", + "es6-symbol": "^3.1" + } + }, + "node_modules/es6-symbol": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/es6-symbol/-/es6-symbol-3.1.1.tgz", + "integrity": "sha1-vwDvT9q2uhtG7Le2KbTH7VcVzHc=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "~0.10.14" + } + }, + "node_modules/es6-weak-map": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/es6-weak-map/-/es6-weak-map-2.0.2.tgz", + "integrity": "sha1-XjqzIlH/0VOKH45f+hNXdy+S2W8=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "^0.10.14", + "es6-iterator": "^2.0.1", + "es6-symbol": "^3.1.1" + } + }, + "node_modules/event-emitter": { + "version": "0.3.5", + "resolved": "https://registry.npmjs.org/event-emitter/-/event-emitter-0.3.5.tgz", + "integrity": "sha1-34xp7vFkeSPHFXuc6DhAYQsCzDk=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "~0.10.14" + } + }, + "node_modules/events": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/events/-/events-1.1.1.tgz", + "integrity": "sha1-nr23Y1rQmccNzEwqH1AEKI6L2SQ=", + "dev": true, + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/evp_bytestokey": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/evp_bytestokey/-/evp_bytestokey-1.0.3.tgz", + "integrity": "sha512-/f2Go4TognH/KvCISP7OUsHn85hT9nUkxxA9BEWxFn+Oj9o8ZNLm/40hdlgSLyuOimsrTKLUMEorQexp/aPQeA==", + "dev": true, + "dependencies": { + "md5.js": "^1.3.4", + "safe-buffer": "^5.1.1" + } + }, + "node_modules/expand-brackets": { + "version": "2.1.4", + "resolved": "https://registry.npmjs.org/expand-brackets/-/expand-brackets-2.1.4.tgz", + "integrity": "sha1-t3c14xXOMPa27/D4OwQVGiJEliI=", + "dev": true, + "dependencies": { + "debug": "^2.3.3", + "define-property": "^0.2.5", + "extend-shallow": "^2.0.1", + "posix-character-classes": "^0.1.0", + "regex-not": "^1.0.0", + "snapdragon": "^0.8.1", + "to-regex": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/expand-brackets/node_modules/debug": { + "version": "2.6.9", + "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", + "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", + "dev": true, + "dependencies": { + "ms": "2.0.0" + } + }, + "node_modules/expand-brackets/node_modules/define-property": { + "version": "0.2.5", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-0.2.5.tgz", + "integrity": "sha1-w1se+RjsPJkPmlvFe+BKrOxcgRY=", + "dev": true, + "dependencies": { + "is-descriptor": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/expand-brackets/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/expand-brackets/node_modules/ms": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", + "integrity": "sha1-VgiurfwAvmwpAd9fmGF4jeDVl8g=", + "dev": true + }, + "node_modules/expand-tilde": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/expand-tilde/-/expand-tilde-2.0.2.tgz", + "integrity": "sha1-l+gBqgUt8CRU3kawK/YhZCzchQI=", + "dev": true, + "dependencies": { + "homedir-polyfill": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extend": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/extend/-/extend-3.0.2.tgz", + "integrity": "sha512-fjquC59cD7CyW6urNXK0FBufkZcoiGG80wTuPujX590cB5Ttln20E2UB4S/WARVqhXffZl2LNgS+gQdPIIim/g==", + "dev": true + }, + "node_modules/extend-shallow": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-3.0.2.tgz", + "integrity": "sha1-Jqcarwc7OfshJxcnRhMcJwQCjbg=", + "dev": true, + "dependencies": { + "assign-symbols": "^1.0.0", + "is-extendable": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extend-shallow/node_modules/is-extendable": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/is-extendable/-/is-extendable-1.0.1.tgz", + "integrity": "sha512-arnXMxT1hhoKo9k1LZdmlNyJdDDfy2v0fXjFlmok4+i8ul/6WlbVge9bhM74OpNPQPMGUToDtz+KXa1PneJxOA==", + "dev": true, + "dependencies": { + "is-plain-object": "^2.0.4" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/extglob/-/extglob-2.0.4.tgz", + "integrity": "sha512-Nmb6QXkELsuBr24CJSkilo6UHHgbekK5UiZgfE6UHD3Eb27YC6oD+bhcT+tJ6cl8dmsgdQxnWlcry8ksBIBLpw==", + "dev": true, + "dependencies": { + "array-unique": "^0.3.2", + "define-property": "^1.0.0", + "expand-brackets": "^2.1.4", + "extend-shallow": "^2.0.1", + "fragment-cache": "^0.2.1", + "regex-not": "^1.0.0", + "snapdragon": "^0.8.1", + "to-regex": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob/node_modules/define-property": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-1.0.0.tgz", + "integrity": "sha1-dp66rz9KY6rTr56NMEybvnm/sOY=", + "dev": true, + "dependencies": { + "is-descriptor": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob/node_modules/is-accessor-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-accessor-descriptor/-/is-accessor-descriptor-1.0.0.tgz", + "integrity": "sha512-m5hnHTkcVsPfqx3AKlyttIPb7J+XykHvJP2B9bZDjlhLIoEq4XoK64Vg7boZlVWYK6LUY94dYPEE7Lh0ZkZKcQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob/node_modules/is-data-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-data-descriptor/-/is-data-descriptor-1.0.0.tgz", + "integrity": "sha512-jbRXy1FmtAoCjQkVmIVYwuuqDFUbaOeDjmed1tOGPrsMhtJA4rD9tkgA0F1qJ3gRFRXcHYVkdeaP50Q5rE/jLQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/extglob/node_modules/is-descriptor": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-descriptor/-/is-descriptor-1.0.2.tgz", + "integrity": "sha512-2eis5WqQGV7peooDyLmNEPUrps9+SXX5c9pL3xEB+4e9HnGuDa7mB7kHxHw4CbqS9k1T2hOH3miL8n8WtiYVtg==", + "dev": true, + "dependencies": { + "is-accessor-descriptor": "^1.0.0", + "is-data-descriptor": "^1.0.0", + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fancy-log": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/fancy-log/-/fancy-log-1.3.2.tgz", + "integrity": "sha1-9BEl49hPLn2JpD0G2VjI94vha+E=", + "dev": true, + "dependencies": { + "ansi-gray": "^0.1.1", + "color-support": "^1.1.3", + "time-stamp": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/fill-range": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/fill-range/-/fill-range-4.0.0.tgz", + "integrity": "sha1-1USBHUKPmOsGpj3EAtJAPDKMOPc=", + "dev": true, + "dependencies": { + "extend-shallow": "^2.0.1", + "is-number": "^3.0.0", + "repeat-string": "^1.6.1", + "to-regex-range": "^2.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fill-range/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/find-up": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/find-up/-/find-up-1.1.2.tgz", + "integrity": "sha1-ay6YIrGizgpgq2TWEOzK1TyyTQ8=", + "dev": true, + "dependencies": { + "path-exists": "^2.0.0", + "pinkie-promise": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/findup-sync": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/findup-sync/-/findup-sync-2.0.0.tgz", + "integrity": "sha1-kyaxSIwi0aYIhlCoaQGy2akKLLw=", + "dev": true, + "dependencies": { + "detect-file": "^1.0.0", + "is-glob": "^3.1.0", + "micromatch": "^3.0.4", + "resolve-dir": "^1.0.1" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/findup-sync/node_modules/is-glob": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-3.1.0.tgz", + "integrity": "sha1-e6WuJCF4BKxwcHuWkiVnSGzD6Eo=", + "dev": true, + "dependencies": { + "is-extglob": "^2.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fined": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/fined/-/fined-1.1.0.tgz", + "integrity": "sha1-s33IRLdqL15wgeiE98CuNE8VNHY=", + "dev": true, + "dependencies": { + "expand-tilde": "^2.0.2", + "is-plain-object": "^2.0.3", + "object.defaults": "^1.1.0", + "object.pick": "^1.2.0", + "parse-filepath": "^1.0.1" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/flagged-respawn": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/flagged-respawn/-/flagged-respawn-1.0.0.tgz", + "integrity": "sha1-Tnmumy6zi/hrO7Vr8+ClaqX8q9c=", + "dev": true, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/flush-write-stream": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/flush-write-stream/-/flush-write-stream-1.0.3.tgz", + "integrity": "sha512-calZMC10u0FMUqoiunI2AiGIIUtUIvifNwkHhNupZH4cbNnW1Itkoh/Nf5HFYmDrwWPjrUxpkZT0KhuCq0jmGw==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "readable-stream": "^2.0.4" + } + }, + "node_modules/for-in": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/for-in/-/for-in-1.0.2.tgz", + "integrity": "sha1-gQaNKVqBQuwKxybG4iAMMPttXoA=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/for-own": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/for-own/-/for-own-1.0.0.tgz", + "integrity": "sha1-xjMy9BXO3EsE2/5wz4NklMU8tEs=", + "dev": true, + "dependencies": { + "for-in": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fragment-cache": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/fragment-cache/-/fragment-cache-0.2.1.tgz", + "integrity": "sha1-QpD60n8T6Jvn8zeZxrxaCr//DRk=", + "dev": true, + "dependencies": { + "map-cache": "^0.2.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fs-mkdirp-stream": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs-mkdirp-stream/-/fs-mkdirp-stream-1.0.0.tgz", + "integrity": "sha1-C3gV/DIBxqaeFNuYzgmMFpNSWes=", + "dev": true, + "dependencies": { + "graceful-fs": "^4.1.11", + "through2": "^2.0.3" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/fs.realpath": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", + "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=", + "dev": true + }, + "node_modules/fsevents": { + "version": "1.2.4", + "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-1.2.4.tgz", + "integrity": "sha512-z8H8/diyk76B7q5wg+Ud0+CqzcAF3mBBI/bA5ne5zrRUUIvNkJY//D3BqyH571KuAC4Nr7Rw7CjWX4r0y9DvNg==", + "bundleDependencies": [ + "abbrev", + "ansi-regex", + "aproba", + "are-we-there-yet", + "balanced-match", + "brace-expansion", + "chownr", + "code-point-at", + "concat-map", + "console-control-strings", + "core-util-is", + "debug", + "deep-extend", + "delegates", + "detect-libc", + "fs-minipass", + "fs.realpath", + "gauge", + "glob", + "has-unicode", + "iconv-lite", + "ignore-walk", + "inflight", + "inherits", + "ini", + "is-fullwidth-code-point", + "isarray", + "minimatch", + "minimist", + "minipass", + "minizlib", + "mkdirp", + "ms", + "needle", + "node-pre-gyp", + "nopt", + "npm-bundled", + "npm-packlist", + "npmlog", + "number-is-nan", + "object-assign", + "once", + "os-homedir", + "os-tmpdir", + "osenv", + "path-is-absolute", + "process-nextick-args", + "rc", + "readable-stream", + "rimraf", + "safe-buffer", + "safer-buffer", + "sax", + "semver", + "set-blocking", + "signal-exit", + "string-width", + "string_decoder", + "strip-ansi", + "strip-json-comments", + "tar", + "util-deprecate", + "wide-align", + "wrappy", + "yallist" + ], + "dev": true, + "hasInstallScript": true, + "optional": true, + "os": [ + "darwin" + ], + "dependencies": { + "nan": "^2.9.2", + "node-pre-gyp": "^0.10.0" + }, + "engines": { + "node": ">=0.8.0" + } + }, + "node_modules/fsevents/node_modules/abbrev": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/abbrev/-/abbrev-1.1.1.tgz", + "integrity": "sha512-nne9/IiQ/hzIhY6pdDnbBtz7DjPTKrY00P/zvPSm5pOFkl6xuGrGnXn/VtTNNfNtAfZ9/1RtehkszU9qcTii0Q==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/ansi-regex": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-2.1.1.tgz", + "integrity": "sha1-w7M6te42DYbg5ijwRorn7yfWVN8=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/aproba": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/aproba/-/aproba-1.2.0.tgz", + "integrity": "sha512-Y9J6ZjXtoYh8RnXVCMOU/ttDmk1aBjunq9vO0ta5x85WDQiQfUF9sIPBITdbiiIVcBo03Hi3jMxigBtsddlXRw==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/are-we-there-yet": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/are-we-there-yet/-/are-we-there-yet-1.1.4.tgz", + "integrity": "sha1-u13KOCu5TwXhUZQ3PRb9O6HKEQ0=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "delegates": "^1.0.0", + "readable-stream": "^2.0.6" + } + }, + "node_modules/fsevents/node_modules/balanced-match": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.0.tgz", + "integrity": "sha1-ibTRmasr7kneFk6gK4nORi1xt2c=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/brace-expansion": { + "version": "1.1.11", + "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", + "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "balanced-match": "^1.0.0", + "concat-map": "0.0.1" + } + }, + "node_modules/fsevents/node_modules/chownr": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/chownr/-/chownr-1.0.1.tgz", + "integrity": "sha1-4qdQQqlVGQi+vSW4Uj1fl2nXkYE=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/code-point-at": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/code-point-at/-/code-point-at-1.1.0.tgz", + "integrity": "sha1-DQcLTQQ6W+ozovGkDi7bPZpMz3c=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/concat-map": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", + "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/console-control-strings": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/console-control-strings/-/console-control-strings-1.1.0.tgz", + "integrity": "sha1-PXz0Rk22RG6mRL9LOVB/mFEAjo4=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/core-util-is": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.2.tgz", + "integrity": "sha1-tf1UIgqivFq1eqtxQMlAdUUDwac=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/debug": { + "version": "2.6.9", + "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", + "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "ms": "2.0.0" + } + }, + "node_modules/fsevents/node_modules/deep-extend": { + "version": "0.5.1", + "resolved": "https://registry.npmjs.org/deep-extend/-/deep-extend-0.5.1.tgz", + "integrity": "sha512-N8vBdOa+DF7zkRrDCsaOXoCs/E2fJfx9B9MrKnnSiHNh4ws7eSys6YQE4KvT1cecKmOASYQBhbKjeuDD9lT81w==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "iojs": ">=1.0.0", + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/delegates": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/delegates/-/delegates-1.0.0.tgz", + "integrity": "sha1-hMbhWbgZBP3KWaDvRM2HDTElD5o=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/detect-libc": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/detect-libc/-/detect-libc-1.0.3.tgz", + "integrity": "sha1-+hN8S9aY7fVc1c0CrFWfkaTEups=", + "dev": true, + "inBundle": true, + "license": "Apache-2.0", + "optional": true, + "bin": { + "detect-libc": "bin/detect-libc.js" + }, + "engines": { + "node": ">=0.10" + } + }, + "node_modules/fsevents/node_modules/fs-minipass": { + "version": "1.2.5", + "resolved": "https://registry.npmjs.org/fs-minipass/-/fs-minipass-1.2.5.tgz", + "integrity": "sha512-JhBl0skXjUPCFH7x6x61gQxrKyXsxB5gcgePLZCwfyCGGsTISMoIeObbrvVeP6Xmyaudw4TT43qV2Gz+iyd2oQ==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "minipass": "^2.2.1" + } + }, + "node_modules/fsevents/node_modules/fs.realpath": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", + "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/gauge": { + "version": "2.7.4", + "resolved": "https://registry.npmjs.org/gauge/-/gauge-2.7.4.tgz", + "integrity": "sha1-LANAXHU4w51+s3sxcCLjJfsBi/c=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "aproba": "^1.0.3", + "console-control-strings": "^1.0.0", + "has-unicode": "^2.0.0", + "object-assign": "^4.1.0", + "signal-exit": "^3.0.0", + "string-width": "^1.0.1", + "strip-ansi": "^3.0.1", + "wide-align": "^1.1.0" + } + }, + "node_modules/fsevents/node_modules/glob": { + "version": "7.1.2", + "resolved": "https://registry.npmjs.org/glob/-/glob-7.1.2.tgz", + "integrity": "sha512-MJTUg1kjuLeQCJ+ccE4Vpa6kKVXkPYJ2mOCQyUuKLcLQsdrMCpBPUi8qVE6+YuaJkozeA9NusTAw3hLr8Xe5EQ==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "fs.realpath": "^1.0.0", + "inflight": "^1.0.4", + "inherits": "2", + "minimatch": "^3.0.4", + "once": "^1.3.0", + "path-is-absolute": "^1.0.0" + }, + "engines": { + "node": "*" + } + }, + "node_modules/fsevents/node_modules/has-unicode": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/has-unicode/-/has-unicode-2.0.1.tgz", + "integrity": "sha1-4Ob+aijPUROIVeCG0Wkedx3iqLk=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/iconv-lite": { + "version": "0.4.21", + "resolved": "https://registry.npmjs.org/iconv-lite/-/iconv-lite-0.4.21.tgz", + "integrity": "sha512-En5V9za5mBt2oUA03WGD3TwDv0MKAruqsuxstbMUZaj9W9k/m1CV/9py3l0L5kw9Bln8fdHQmzHSYtvpvTLpKw==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "safer-buffer": "^2.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/ignore-walk": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/ignore-walk/-/ignore-walk-3.0.1.tgz", + "integrity": "sha512-DTVlMx3IYPe0/JJcYP7Gxg7ttZZu3IInhuEhbchuqneY9wWe5Ojy2mXLBaQFUQmo0AW2r3qG7m1mg86js+gnlQ==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "minimatch": "^3.0.4" + } + }, + "node_modules/fsevents/node_modules/inflight": { + "version": "1.0.6", + "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", + "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "once": "^1.3.0", + "wrappy": "1" + } + }, + "node_modules/fsevents/node_modules/inherits": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", + "integrity": "sha1-Yzwsg+PaQqUC9SRmAiSA9CCCYd4=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/ini": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/ini/-/ini-1.3.5.tgz", + "integrity": "sha512-RZY5huIKCMRWDUqZlEi72f/lmXKMvuszcMBduliQ3nnWbx9X/ZBQO7DijMEYS9EhHBb2qacRUMtC7svLwe0lcw==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "engines": { + "node": "*" + } + }, + "node_modules/fsevents/node_modules/is-fullwidth-code-point": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-fullwidth-code-point/-/is-fullwidth-code-point-1.0.0.tgz", + "integrity": "sha1-754xOG8DGn8NZDr4L95QxFfvAMs=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "number-is-nan": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/minimatch": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", + "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "brace-expansion": "^1.1.7" + }, + "engines": { + "node": "*" + } + }, + "node_modules/fsevents/node_modules/minimist": { + "version": "0.0.8", + "resolved": "https://registry.npmjs.org/minimist/-/minimist-0.0.8.tgz", + "integrity": "sha1-hX/Kv8M5fSYluCKCYuhqp6ARsF0=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/minipass": { + "version": "2.2.4", + "resolved": "https://registry.npmjs.org/minipass/-/minipass-2.2.4.tgz", + "integrity": "sha512-hzXIWWet/BzWhYs2b+u7dRHlruXhwdgvlTMDKC6Cb1U7ps6Ac6yQlR39xsbjWJE377YTCtKwIXIpJ5oP+j5y8g==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "safe-buffer": "^5.1.1", + "yallist": "^3.0.0" + } + }, + "node_modules/fsevents/node_modules/minizlib": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/minizlib/-/minizlib-1.1.0.tgz", + "integrity": "sha512-4T6Ur/GctZ27nHfpt9THOdRZNgyJ9FZchYO1ceg5S8Q3DNLCKYy44nCZzgCJgcvx2UM8czmqak5BCxJMrq37lA==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "minipass": "^2.2.1" + } + }, + "node_modules/fsevents/node_modules/mkdirp": { + "version": "0.5.1", + "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.1.tgz", + "integrity": "sha1-MAV0OOrGz3+MR2fzhkjWaX11yQM=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "minimist": "0.0.8" + }, + "bin": { + "mkdirp": "bin/cmd.js" + } + }, + "node_modules/fsevents/node_modules/ms": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", + "integrity": "sha1-VgiurfwAvmwpAd9fmGF4jeDVl8g=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/needle": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/needle/-/needle-2.2.0.tgz", + "integrity": "sha512-eFagy6c+TYayorXw/qtAdSvaUpEbBsDwDyxYFgLZ0lTojfH7K+OdBqAF7TAFwDokJaGpubpSGG0wO3iC0XPi8w==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "debug": "^2.1.2", + "iconv-lite": "^0.4.4", + "sax": "^1.2.4" + }, + "bin": { + "needle": "bin/needle" + }, + "engines": { + "node": ">= 0.10.x" + } + }, + "node_modules/fsevents/node_modules/node-pre-gyp": { + "version": "0.10.0", + "resolved": "https://registry.npmjs.org/node-pre-gyp/-/node-pre-gyp-0.10.0.tgz", + "integrity": "sha512-G7kEonQLRbcA/mOoFoxvlMrw6Q6dPf92+t/l0DFSMuSlDoWaI9JWIyPwK0jyE1bph//CUEL65/Fz1m2vJbmjQQ==", + "dev": true, + "inBundle": true, + "license": "BSD-3-Clause", + "optional": true, + "dependencies": { + "detect-libc": "^1.0.2", + "mkdirp": "^0.5.1", + "needle": "^2.2.0", + "nopt": "^4.0.1", + "npm-packlist": "^1.1.6", + "npmlog": "^4.0.2", + "rc": "^1.1.7", + "rimraf": "^2.6.1", + "semver": "^5.3.0", + "tar": "^4" + }, + "bin": { + "node-pre-gyp": "bin/node-pre-gyp" + } + }, + "node_modules/fsevents/node_modules/nopt": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/nopt/-/nopt-4.0.1.tgz", + "integrity": "sha1-0NRoWv1UFRk8jHUFYC0NF81kR00=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "abbrev": "1", + "osenv": "^0.1.4" + }, + "bin": { + "nopt": "bin/nopt.js" + } + }, + "node_modules/fsevents/node_modules/npm-bundled": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/npm-bundled/-/npm-bundled-1.0.3.tgz", + "integrity": "sha512-ByQ3oJ/5ETLyglU2+8dBObvhfWXX8dtPZDMePCahptliFX2iIuhyEszyFk401PZUNQH20vvdW5MLjJxkwU80Ow==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/npm-packlist": { + "version": "1.1.10", + "resolved": "https://registry.npmjs.org/npm-packlist/-/npm-packlist-1.1.10.tgz", + "integrity": "sha512-AQC0Dyhzn4EiYEfIUjCdMl0JJ61I2ER9ukf/sLxJUcZHfo+VyEfz2rMJgLZSS1v30OxPQe1cN0LZA1xbcaVfWA==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "ignore-walk": "^3.0.1", + "npm-bundled": "^1.0.1" + } + }, + "node_modules/fsevents/node_modules/npmlog": { + "version": "4.1.2", + "resolved": "https://registry.npmjs.org/npmlog/-/npmlog-4.1.2.tgz", + "integrity": "sha512-2uUqazuKlTaSI/dC8AzicUck7+IrEaOnN/e0jd3Xtt1KcGpwx30v50mL7oPyr/h9bL3E4aZccVwpwP+5W9Vjkg==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "are-we-there-yet": "~1.1.2", + "console-control-strings": "~1.1.0", + "gauge": "~2.7.3", + "set-blocking": "~2.0.0" + } + }, + "node_modules/fsevents/node_modules/number-is-nan": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/number-is-nan/-/number-is-nan-1.0.1.tgz", + "integrity": "sha1-CXtgK1NCKlIsGvuHkDGDNpQaAR0=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/object-assign": { + "version": "4.1.1", + "resolved": "https://registry.npmjs.org/object-assign/-/object-assign-4.1.1.tgz", + "integrity": "sha1-IQmtx5ZYh8/AXLvUQsrIv7s2CGM=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/once": { + "version": "1.4.0", + "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", + "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "wrappy": "1" + } + }, + "node_modules/fsevents/node_modules/os-homedir": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/os-homedir/-/os-homedir-1.0.2.tgz", + "integrity": "sha1-/7xJiDNuDoM94MFox+8VISGqf7M=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/os-tmpdir": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/os-tmpdir/-/os-tmpdir-1.0.2.tgz", + "integrity": "sha1-u+Z0BseaqFxc/sdm/lc0VV36EnQ=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/osenv": { + "version": "0.1.5", + "resolved": "https://registry.npmjs.org/osenv/-/osenv-0.1.5.tgz", + "integrity": "sha512-0CWcCECdMVc2Rw3U5w9ZjqX6ga6ubk1xDVKxtBQPK7wis/0F2r9T6k4ydGYhecl7YUBxBVxhL5oisPsNxAPe2g==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "os-homedir": "^1.0.0", + "os-tmpdir": "^1.0.0" + } + }, + "node_modules/fsevents/node_modules/path-is-absolute": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", + "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/process-nextick-args": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.0.tgz", + "integrity": "sha512-MtEC1TqN0EU5nephaJ4rAtThHtC86dNN9qCuEhtshvpVBkAW5ZO7BASN9REnF9eoXGcRub+pFuKEpOHE+HbEMw==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/rc": { + "version": "1.2.7", + "resolved": "https://registry.npmjs.org/rc/-/rc-1.2.7.tgz", + "integrity": "sha512-LdLD8xD4zzLsAT5xyushXDNscEjB7+2ulnl8+r1pnESlYtlJtVSoCMBGr30eDRJ3+2Gq89jK9P9e4tCEH1+ywA==", + "dev": true, + "inBundle": true, + "license": "(BSD-2-Clause OR MIT OR Apache-2.0)", + "optional": true, + "dependencies": { + "deep-extend": "^0.5.1", + "ini": "~1.3.0", + "minimist": "^1.2.0", + "strip-json-comments": "~2.0.1" + }, + "bin": { + "rc": "cli.js" + } + }, + "node_modules/fsevents/node_modules/rc/node_modules/minimist": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.0.tgz", + "integrity": "sha1-o1AIsg9BOD7sH7kU9M1d95omQoQ=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/readable-stream": { + "version": "2.3.6", + "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.6.tgz", + "integrity": "sha512-tQtKA9WIAhBF3+VLAseyMqZeBjW0AHJoxOtYqSUZNJxauErmLbVm2FW1y+J/YA9dUrAC39ITejlZWhVIwawkKw==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "core-util-is": "~1.0.0", + "inherits": "~2.0.3", + "isarray": "~1.0.0", + "process-nextick-args": "~2.0.0", + "safe-buffer": "~5.1.1", + "string_decoder": "~1.1.1", + "util-deprecate": "~1.0.1" + } + }, + "node_modules/fsevents/node_modules/rimraf": { + "version": "2.6.2", + "resolved": "https://registry.npmjs.org/rimraf/-/rimraf-2.6.2.tgz", + "integrity": "sha512-lreewLK/BlghmxtfH36YYVg1i8IAce4TI7oao75I1g245+6BctqTVQiBP3YUJ9C6DQOXJmkYR9X9fCLtCOJc5w==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "glob": "^7.0.5" + }, + "bin": { + "rimraf": "bin.js" + } + }, + "node_modules/fsevents/node_modules/safe-buffer": { + "version": "5.1.1", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.1.tgz", + "integrity": "sha512-kKvNJn6Mm93gAczWVJg7wH+wGYWNrDHdWvpUmHyEsgCtIwwo3bqPtV4tR5tuPaUhTOo/kvhVwd8XwwOllGYkbg==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/safer-buffer": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", + "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/sax": { + "version": "1.2.4", + "resolved": "https://registry.npmjs.org/sax/-/sax-1.2.4.tgz", + "integrity": "sha512-NqVDv9TpANUjFm0N8uM5GxL36UgKi9/atZw+x7YFnQ8ckwFGKrl4xX4yWtrey3UJm5nP1kUbnYgLopqWNSRhWw==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/semver": { + "version": "5.5.0", + "resolved": "https://registry.npmjs.org/semver/-/semver-5.5.0.tgz", + "integrity": "sha512-4SJ3dm0WAwWy/NVeioZh5AntkdJoWKxHxcmyP622fOkgHa4z3R0TdBJICINyaSDE6uNwVc8gZr+ZinwZAH4xIA==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "bin": { + "semver": "bin/semver" + } + }, + "node_modules/fsevents/node_modules/set-blocking": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/set-blocking/-/set-blocking-2.0.0.tgz", + "integrity": "sha1-BF+XgtARrppoA93TgrJDkrPYkPc=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/signal-exit": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.2.tgz", + "integrity": "sha1-tf3AjxKH6hF4Yo5BXiUTK3NkbG0=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "safe-buffer": "~5.1.0" + } + }, + "node_modules/fsevents/node_modules/string-width": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/string-width/-/string-width-1.0.2.tgz", + "integrity": "sha1-EYvfW4zcUaKn5w0hHgfisLmxB9M=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "code-point-at": "^1.0.0", + "is-fullwidth-code-point": "^1.0.0", + "strip-ansi": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/strip-ansi": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-3.0.1.tgz", + "integrity": "sha1-ajhfuIU9lS1f8F0Oiq+UJ43GPc8=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "dependencies": { + "ansi-regex": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/strip-json-comments": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/strip-json-comments/-/strip-json-comments-2.0.1.tgz", + "integrity": "sha1-PFMZQukIwml8DsNEhYwobHygpgo=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/fsevents/node_modules/tar": { + "version": "4.4.1", + "resolved": "https://registry.npmjs.org/tar/-/tar-4.4.1.tgz", + "integrity": "sha512-O+v1r9yN4tOsvl90p5HAP4AEqbYhx4036AGMm075fH9F8Qwi3oJ+v4u50FkT/KkvywNGtwkk0zRI+8eYm1X/xg==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "chownr": "^1.0.1", + "fs-minipass": "^1.2.5", + "minipass": "^2.2.4", + "minizlib": "^1.1.0", + "mkdirp": "^0.5.0", + "safe-buffer": "^5.1.1", + "yallist": "^3.0.2" + }, + "engines": { + "node": ">=4.5" + } + }, + "node_modules/fsevents/node_modules/util-deprecate": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", + "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=", + "dev": true, + "inBundle": true, + "license": "MIT", + "optional": true + }, + "node_modules/fsevents/node_modules/wide-align": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/wide-align/-/wide-align-1.1.2.tgz", + "integrity": "sha512-ijDLlyQ7s6x1JgCLur53osjm/UXUYD9+0PbYKrBsYisYXzCxN+HC3mYDNy/dWdmf3AwqwU3CXwDCvsNgGK1S0w==", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true, + "dependencies": { + "string-width": "^1.0.2" + } + }, + "node_modules/fsevents/node_modules/wrappy": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", + "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/fsevents/node_modules/yallist": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/yallist/-/yallist-3.0.2.tgz", + "integrity": "sha1-hFK0u36Dx8GI2AQcGoN8dz1ti7k=", + "dev": true, + "inBundle": true, + "license": "ISC", + "optional": true + }, + "node_modules/function-bind": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", + "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==", + "dev": true + }, + "node_modules/fuse.js": { + "version": "3.3.0", + "resolved": "https://registry.npmjs.org/fuse.js/-/fuse.js-3.3.0.tgz", + "integrity": "sha512-ESBRkGLWMuVkapqYCcNO1uqMg5qbCKkgb+VS6wsy17Rix0/cMS9kSOZoYkjH8Ko//pgJ/EEGu0GTjk2mjX2LGQ==" + }, + "node_modules/get-assigned-identifiers": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/get-assigned-identifiers/-/get-assigned-identifiers-1.2.0.tgz", + "integrity": "sha512-mBBwmeGTrxEMO4pMaaf/uUEFHnYtwr8FTe8Y/mer4rcV/bye0qGm6pw1bGZFGStxC5O76c5ZAVBGnqHmOaJpdQ==", + "dev": true + }, + "node_modules/get-caller-file": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/get-caller-file/-/get-caller-file-1.0.3.tgz", + "integrity": "sha512-3t6rVToeoZfYSGd8YoLFR2DJkiQrIiUrGcjvFX2mDw3bn6k2OtwHN0TNCLbBO+w8qTvimhDkv+LSscbJY1vE6w==", + "dev": true + }, + "node_modules/get-value": { + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/get-value/-/get-value-2.0.6.tgz", + "integrity": "sha1-3BXKHGcjh8p2vTesCjlbogQqLCg=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/glob": { + "version": "7.1.3", + "resolved": "https://registry.npmjs.org/glob/-/glob-7.1.3.tgz", + "integrity": "sha512-vcfuiIxogLV4DlGBHIUOwI0IbrJ8HWPc4MU7HzviGeNho/UJDfi6B5p3sHeWIQ0KGIU0Jpxi5ZHxemQfLkkAwQ==", + "dev": true, + "dependencies": { + "fs.realpath": "^1.0.0", + "inflight": "^1.0.4", + "inherits": "2", + "minimatch": "^3.0.4", + "once": "^1.3.0", + "path-is-absolute": "^1.0.0" + }, + "engines": { + "node": "*" + } + }, + "node_modules/glob-parent": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-3.1.0.tgz", + "integrity": "sha1-nmr2KZ2NO9K9QEMIMr0RPfkGxa4=", + "dev": true, + "dependencies": { + "is-glob": "^3.1.0", + "path-dirname": "^1.0.0" + } + }, + "node_modules/glob-parent/node_modules/is-glob": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-3.1.0.tgz", + "integrity": "sha1-e6WuJCF4BKxwcHuWkiVnSGzD6Eo=", + "dev": true, + "dependencies": { + "is-extglob": "^2.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/glob-stream": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/glob-stream/-/glob-stream-6.1.0.tgz", + "integrity": "sha1-cEXJlBOz65SIjYOrRtC0BMx73eQ=", + "dev": true, + "dependencies": { + "extend": "^3.0.0", + "glob": "^7.1.1", + "glob-parent": "^3.1.0", + "is-negated-glob": "^1.0.0", + "ordered-read-streams": "^1.0.0", + "pumpify": "^1.3.5", + "readable-stream": "^2.1.5", + "remove-trailing-separator": "^1.0.1", + "to-absolute-glob": "^2.0.0", + "unique-stream": "^2.0.2" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/glob-watcher": { + "version": "5.0.1", + "resolved": "https://registry.npmjs.org/glob-watcher/-/glob-watcher-5.0.1.tgz", + "integrity": "sha512-fK92r2COMC199WCyGUblrZKhjra3cyVMDiypDdqg1vsSDmexnbYivK1kNR4QItiNXLKmGlqan469ks67RtNa2g==", + "dev": true, + "dependencies": { + "async-done": "^1.2.0", + "chokidar": "^2.0.0", + "just-debounce": "^1.0.0", + "object.defaults": "^1.1.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/global-modules": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/global-modules/-/global-modules-1.0.0.tgz", + "integrity": "sha512-sKzpEkf11GpOFuw0Zzjzmt4B4UZwjOcG757PPvrfhxcLFbq0wpsgpOqxpxtxFiCG4DtG93M6XRVbF2oGdev7bg==", + "dev": true, + "dependencies": { + "global-prefix": "^1.0.1", + "is-windows": "^1.0.1", + "resolve-dir": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/global-prefix": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/global-prefix/-/global-prefix-1.0.2.tgz", + "integrity": "sha1-2/dDxsFJklk8ZVVoy2btMsASLr4=", + "dev": true, + "dependencies": { + "expand-tilde": "^2.0.2", + "homedir-polyfill": "^1.0.1", + "ini": "^1.3.4", + "is-windows": "^1.0.1", + "which": "^1.2.14" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/glogg": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/glogg/-/glogg-1.0.0.tgz", + "integrity": "sha1-f+DxmfV6yQbPUS/urY+Q7kooT8U=", + "dev": true, + "dependencies": { + "sparkles": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/graceful-fs": { + "version": "4.1.11", + "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.1.11.tgz", + "integrity": "sha1-Dovf5NHduIVNZOBOp8AOKgJuVlg=", + "dev": true, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/gulp": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/gulp/-/gulp-4.0.0.tgz", + "integrity": "sha1-lXZsYB2t5Kd+0+eyttwDiBtZY2Y=", + "dev": true, + "dependencies": { + "glob-watcher": "^5.0.0", + "gulp-cli": "^2.0.0", + "undertaker": "^1.0.0", + "vinyl-fs": "^3.0.0" + }, + "bin": { + "gulp": "bin/gulp.js" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/gulp-sourcemaps": { + "version": "2.6.4", + "resolved": "https://registry.npmjs.org/gulp-sourcemaps/-/gulp-sourcemaps-2.6.4.tgz", + "integrity": "sha1-y7IAhFCxvM5s0jv5gze+dRv24wo=", + "dev": true, + "dependencies": { + "@gulp-sourcemaps/identity-map": "1.X", + "@gulp-sourcemaps/map-sources": "1.X", + "acorn": "5.X", + "convert-source-map": "1.X", + "css": "2.X", + "debug-fabulous": "1.X", + "detect-newline": "2.X", + "graceful-fs": "4.X", + "source-map": "~0.6.0", + "strip-bom-string": "1.X", + "through2": "2.X" + }, + "engines": { + "node": ">=4" + } + }, + "node_modules/gulp-sourcemaps/node_modules/acorn": { + "version": "5.7.3", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-5.7.3.tgz", + "integrity": "sha512-T/zvzYRfbVojPWahDsE5evJdHb3oJoQfFbsrKM7w5Zcs++Tr257tia3BmMP8XYVjp1S9RZXQMh7gao96BlqZOw==", + "dev": true, + "bin": { + "acorn": "bin/acorn" + }, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/gulp-sourcemaps/node_modules/source-map": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/gulp-uglify": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/gulp-uglify/-/gulp-uglify-3.0.1.tgz", + "integrity": "sha512-KVffbGY9d4Wv90bW/B1KZJyunLMyfHTBbilpDvmcrj5Go0/a1G3uVpt+1gRBWSw/11dqR3coJ1oWNTt1AiXuWQ==", + "dev": true, + "dependencies": { + "gulplog": "^1.0.0", + "has-gulplog": "^0.1.0", + "lodash": "^4.13.1", + "make-error-cause": "^1.1.1", + "safe-buffer": "^5.1.2", + "through2": "^2.0.0", + "uglify-js": "^3.0.5", + "vinyl-sourcemaps-apply": "^0.2.0" + } + }, + "node_modules/gulp-uglify/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/gulp/node_modules/concat-stream": { + "version": "1.6.2", + "resolved": "https://registry.npmjs.org/concat-stream/-/concat-stream-1.6.2.tgz", + "integrity": "sha512-27HBghJxjiZtIk3Ycvn/4kbJk/1uZuJFfuPEns6LaEvpvG1f0hTea8lilrouyo9mVc2GWdcEZ8OLoGmSADlrCw==", + "dev": true, + "engines": [ + "node >= 0.8" + ], + "dependencies": { + "buffer-from": "^1.0.0", + "inherits": "^2.0.3", + "readable-stream": "^2.2.2", + "typedarray": "^0.0.6" + } + }, + "node_modules/gulp/node_modules/gulp-cli": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/gulp-cli/-/gulp-cli-2.0.1.tgz", + "integrity": "sha512-RxujJJdN8/O6IW2nPugl7YazhmrIEjmiVfPKrWt68r71UCaLKS71Hp0gpKT+F6qOUFtr7KqtifDKaAJPRVvMYQ==", + "dev": true, + "dependencies": { + "ansi-colors": "^1.0.1", + "archy": "^1.0.0", + "array-sort": "^1.0.0", + "color-support": "^1.1.3", + "concat-stream": "^1.6.0", + "copy-props": "^2.0.1", + "fancy-log": "^1.3.2", + "gulplog": "^1.0.0", + "interpret": "^1.1.0", + "isobject": "^3.0.1", + "liftoff": "^2.5.0", + "matchdep": "^2.0.0", + "mute-stdout": "^1.0.0", + "pretty-hrtime": "^1.0.0", + "replace-homedir": "^1.0.0", + "semver-greatest-satisfied-range": "^1.1.0", + "v8flags": "^3.0.1", + "yargs": "^7.1.0" + }, + "bin": { + "gulp": "bin/gulp.js" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/gulplog": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/gulplog/-/gulplog-1.0.0.tgz", + "integrity": "sha1-4oxNRdBey77YGDY86PnFkmIp/+U=", + "dev": true, + "dependencies": { + "glogg": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/has": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/has/-/has-1.0.3.tgz", + "integrity": "sha512-f2dvO0VU6Oej7RkWJGrehjbzMAjFp5/VKPp5tTpWIV4JHHZK1/BxbFRtf/siA2SWTe09caDmVtYYzWEIbBS4zw==", + "dev": true, + "dependencies": { + "function-bind": "^1.1.1" + }, + "engines": { + "node": ">= 0.4.0" + } + }, + "node_modules/has-gulplog": { + "version": "0.1.0", + "resolved": "https://registry.npmjs.org/has-gulplog/-/has-gulplog-0.1.0.tgz", + "integrity": "sha1-ZBTIKRNpfaUVkDl9r7EvIpZ4Ec4=", + "dev": true, + "dependencies": { + "sparkles": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/has-symbols": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.0.tgz", + "integrity": "sha1-uhqPGvKg/DllD1yFA2dwQSIGO0Q=", + "dev": true, + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/has-value": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-value/-/has-value-1.0.0.tgz", + "integrity": "sha1-GLKB2lhbHFxR3vJMkw7SmgvmsXc=", + "dev": true, + "dependencies": { + "get-value": "^2.0.6", + "has-values": "^1.0.0", + "isobject": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/has-values": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-values/-/has-values-1.0.0.tgz", + "integrity": "sha1-lbC2P+whRmGab+V/51Yo1aOe/k8=", + "dev": true, + "dependencies": { + "is-number": "^3.0.0", + "kind-of": "^4.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/has-values/node_modules/kind-of": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-4.0.0.tgz", + "integrity": "sha1-IIE989cSkosgc3hpGkUGb65y3Vc=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/hash-base": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/hash-base/-/hash-base-3.0.4.tgz", + "integrity": "sha1-X8hoaEfs1zSZQDMZprCj8/auSRg=", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + }, + "engines": { + "node": ">=4" + } + }, + "node_modules/hash.js": { + "version": "1.1.5", + "resolved": "https://registry.npmjs.org/hash.js/-/hash.js-1.1.5.tgz", + "integrity": "sha512-eWI5HG9Np+eHV1KQhisXWwM+4EPPYe5dFX1UZZH7k/E3JzDEazVH+VGlZi6R94ZqImq+A3D1mCEtrFIfg/E7sA==", + "dev": true, + "dependencies": { + "inherits": "^2.0.3", + "minimalistic-assert": "^1.0.1" + } + }, + "node_modules/hmac-drbg": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/hmac-drbg/-/hmac-drbg-1.0.1.tgz", + "integrity": "sha1-0nRXAQJabHdabFRXk+1QL8DGSaE=", + "dev": true, + "dependencies": { + "hash.js": "^1.0.3", + "minimalistic-assert": "^1.0.0", + "minimalistic-crypto-utils": "^1.0.1" + } + }, + "node_modules/homedir-polyfill": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/homedir-polyfill/-/homedir-polyfill-1.0.1.tgz", + "integrity": "sha1-TCu8inWJmP7r9e1oWA921GdotLw=", + "dev": true, + "dependencies": { + "parse-passwd": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/hosted-git-info": { + "version": "2.7.1", + "resolved": "https://registry.npmjs.org/hosted-git-info/-/hosted-git-info-2.7.1.tgz", + "integrity": "sha512-7T/BxH19zbcCTa8XkMlbK5lTo1WtgkFi3GvdWEyNuc4Vex7/9Dqbnpsf4JMydcfj9HCg4zUWFTL3Za6lapg5/w==", + "dev": true + }, + "node_modules/htmlescape": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/htmlescape/-/htmlescape-1.1.1.tgz", + "integrity": "sha1-OgPtwiFLyjtmQko+eVk0lQnLA1E=", + "dev": true, + "engines": { + "node": ">=0.10" + } + }, + "node_modules/https-browserify": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/https-browserify/-/https-browserify-1.0.0.tgz", + "integrity": "sha1-7AbBDgo0wPL68Zn3/X/Hj//QPHM=", + "dev": true + }, + "node_modules/ieee754": { + "version": "1.1.12", + "resolved": "https://registry.npmjs.org/ieee754/-/ieee754-1.1.12.tgz", + "integrity": "sha512-GguP+DRY+pJ3soyIiGPTvdiVXjZ+DbXOxGpXn3eMvNW4x4irjqXm4wHKscC+TfxSJ0yw/S1F24tqdMNsMZTiLA==", + "dev": true + }, + "node_modules/indexof": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/indexof/-/indexof-0.0.1.tgz", + "integrity": "sha1-gtwzbSMrkGIXnQWrMpOmYFn9Q10=", + "dev": true + }, + "node_modules/inflight": { + "version": "1.0.6", + "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", + "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", + "dev": true, + "dependencies": { + "once": "^1.3.0", + "wrappy": "1" + } + }, + "node_modules/inherits": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", + "integrity": "sha1-Yzwsg+PaQqUC9SRmAiSA9CCCYd4=", + "dev": true + }, + "node_modules/ini": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/ini/-/ini-1.3.5.tgz", + "integrity": "sha512-RZY5huIKCMRWDUqZlEi72f/lmXKMvuszcMBduliQ3nnWbx9X/ZBQO7DijMEYS9EhHBb2qacRUMtC7svLwe0lcw==", + "dev": true, + "engines": { + "node": "*" + } + }, + "node_modules/inline-source-map": { + "version": "0.6.2", + "resolved": "https://registry.npmjs.org/inline-source-map/-/inline-source-map-0.6.2.tgz", + "integrity": "sha1-+Tk0ccGKedFyT4Y/o4tYY3Ct4qU=", + "dev": true, + "dependencies": { + "source-map": "~0.5.3" + } + }, + "node_modules/insert-module-globals": { + "version": "7.2.0", + "resolved": "https://registry.npmjs.org/insert-module-globals/-/insert-module-globals-7.2.0.tgz", + "integrity": "sha512-VE6NlW+WGn2/AeOMd496AHFYmE7eLKkUY6Ty31k4og5vmA3Fjuwe9v6ifH6Xx/Hz27QvdoMoviw1/pqWRB09Sw==", + "dev": true, + "dependencies": { + "acorn-node": "^1.5.2", + "combine-source-map": "^0.8.0", + "concat-stream": "^1.6.1", + "is-buffer": "^1.1.0", + "JSONStream": "^1.0.3", + "path-is-absolute": "^1.0.1", + "process": "~0.11.0", + "through2": "^2.0.0", + "undeclared-identifiers": "^1.1.2", + "xtend": "^4.0.0" + }, + "bin": { + "insert-module-globals": "bin/cmd.js" + } + }, + "node_modules/insert-module-globals/node_modules/concat-stream": { + "version": "1.6.2", + "resolved": "https://registry.npmjs.org/concat-stream/-/concat-stream-1.6.2.tgz", + "integrity": "sha512-27HBghJxjiZtIk3Ycvn/4kbJk/1uZuJFfuPEns6LaEvpvG1f0hTea8lilrouyo9mVc2GWdcEZ8OLoGmSADlrCw==", + "dev": true, + "engines": [ + "node >= 0.8" + ], + "dependencies": { + "buffer-from": "^1.0.0", + "inherits": "^2.0.3", + "readable-stream": "^2.2.2", + "typedarray": "^0.0.6" + } + }, + "node_modules/interpret": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/interpret/-/interpret-1.1.0.tgz", + "integrity": "sha1-ftGxQQxqDg94z5XTuEQMY/eLhhQ=", + "dev": true + }, + "node_modules/invert-kv": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/invert-kv/-/invert-kv-1.0.0.tgz", + "integrity": "sha1-EEqOSqym09jNFXqO+L+rLXo//bY=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-absolute": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-absolute/-/is-absolute-1.0.0.tgz", + "integrity": "sha512-dOWoqflvcydARa360Gvv18DZ/gRuHKi2NU/wU5X1ZFzdYfH29nkiNZsF3mp4OJ3H4yo9Mx8A/uAGNzpzPN3yBA==", + "dev": true, + "dependencies": { + "is-relative": "^1.0.0", + "is-windows": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-accessor-descriptor": { + "version": "0.1.6", + "resolved": "https://registry.npmjs.org/is-accessor-descriptor/-/is-accessor-descriptor-0.1.6.tgz", + "integrity": "sha1-qeEss66Nh2cn7u84Q/igiXtcmNY=", + "dev": true, + "dependencies": { + "kind-of": "^3.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-accessor-descriptor/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-arrayish": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/is-arrayish/-/is-arrayish-0.2.1.tgz", + "integrity": "sha1-d8mYQFJ6qOyxqLppe4BkWnqSap0=", + "dev": true + }, + "node_modules/is-binary-path": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/is-binary-path/-/is-binary-path-1.0.1.tgz", + "integrity": "sha1-dfFmQrSA8YenEcgUFh/TpKdlWJg=", + "dev": true, + "dependencies": { + "binary-extensions": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-buffer": { + "version": "1.1.5", + "resolved": "https://registry.npmjs.org/is-buffer/-/is-buffer-1.1.5.tgz", + "integrity": "sha1-Hzsm72E7IUuIy8ojzGwB2Hlh7sw=", + "dev": true + }, + "node_modules/is-builtin-module": { + "version": "1.0.0", + "resolved": "http://registry.npmjs.org/is-builtin-module/-/is-builtin-module-1.0.0.tgz", + "integrity": "sha1-VAVy0096wxGfj3bDDLwbHgN6/74=", + "dev": true, + "dependencies": { + "builtin-modules": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-data-descriptor": { + "version": "0.1.4", + "resolved": "https://registry.npmjs.org/is-data-descriptor/-/is-data-descriptor-0.1.4.tgz", + "integrity": "sha1-C17mSDiOLIYCgueT8YVv7D8wG1Y=", + "dev": true, + "dependencies": { + "kind-of": "^3.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-data-descriptor/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-descriptor": { + "version": "0.1.6", + "resolved": "https://registry.npmjs.org/is-descriptor/-/is-descriptor-0.1.6.tgz", + "integrity": "sha512-avDYr0SB3DwO9zsMov0gKCESFYqCnE4hq/4z3TdUlukEy5t9C0YRq7HLrsN52NAcqXKaepeCD0n+B0arnVG3Hg==", + "dev": true, + "dependencies": { + "is-accessor-descriptor": "^0.1.6", + "is-data-descriptor": "^0.1.4", + "kind-of": "^5.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-descriptor/node_modules/kind-of": { + "version": "5.1.0", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-5.1.0.tgz", + "integrity": "sha512-NGEErnH6F2vUuXDh+OlbcKW7/wOcfdRHaZ7VWtqCztfHri/++YKmP51OdWeGPuqCOba6kk2OTe5d02VmTB80Pw==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-extendable": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/is-extendable/-/is-extendable-0.1.1.tgz", + "integrity": "sha1-YrEQ4omkcUGOPsNqYX1HLjAd/Ik=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-extglob": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", + "integrity": "sha1-qIwCU1eR8C7TfHahueqXc8gz+MI=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-fullwidth-code-point": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-fullwidth-code-point/-/is-fullwidth-code-point-1.0.0.tgz", + "integrity": "sha1-754xOG8DGn8NZDr4L95QxFfvAMs=", + "dev": true, + "dependencies": { + "number-is-nan": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-glob": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-4.0.0.tgz", + "integrity": "sha1-lSHHaEXMJhCoUgPd8ICpWML/q8A=", + "dev": true, + "dependencies": { + "is-extglob": "^2.1.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-negated-glob": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-negated-glob/-/is-negated-glob-1.0.0.tgz", + "integrity": "sha1-aRC8pdqMleeEtXUbl2z1oQ/uNtI=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-number": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/is-number/-/is-number-3.0.0.tgz", + "integrity": "sha1-JP1iAaR4LPUFYcgQJ2r8fRLXEZU=", + "dev": true, + "dependencies": { + "kind-of": "^3.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-number/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-plain-object": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/is-plain-object/-/is-plain-object-2.0.4.tgz", + "integrity": "sha512-h5PpgXkWitc38BBMYawTYMWJHFZJVnBquFE57xFpjB8pJFiF6gZ+bU+WyI/yqXiFR5mdLsgYNaPe8uao6Uv9Og==", + "dev": true, + "dependencies": { + "isobject": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-promise": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/is-promise/-/is-promise-2.1.0.tgz", + "integrity": "sha1-eaKp7OfwlugPNtKy87wWwf9L8/o=", + "dev": true + }, + "node_modules/is-relative": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-relative/-/is-relative-1.0.0.tgz", + "integrity": "sha512-Kw/ReK0iqwKeu0MITLFuj0jbPAmEiOsIwyIXvvbfa6QfmN9pkD1M+8pdk7Rl/dTKbH34/XBFMbgD4iMJhLQbGA==", + "dev": true, + "dependencies": { + "is-unc-path": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-unc-path": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-unc-path/-/is-unc-path-1.0.0.tgz", + "integrity": "sha512-mrGpVd0fs7WWLfVsStvgF6iEJnbjDFZh9/emhRDcGWTduTfNHd9CHeUwH3gYIjdbwo4On6hunkztwOaAw0yllQ==", + "dev": true, + "dependencies": { + "unc-path-regex": "^0.1.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-utf8": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/is-utf8/-/is-utf8-0.2.1.tgz", + "integrity": "sha1-Sw2hRCEE0bM2NA6AeX6GXPOffXI=", + "dev": true + }, + "node_modules/is-valid-glob": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-valid-glob/-/is-valid-glob-1.0.0.tgz", + "integrity": "sha1-Kb8+/3Ab4tTTFdusw5vDn+j2Aao=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-windows": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-windows/-/is-windows-1.0.2.tgz", + "integrity": "sha512-eXK1UInq2bPmjyX6e3VHIzMLobc4J94i4AWn+Hpq3OU5KkrRC96OAcR3PRJ/pGu6m8TRnBHP9dkXQVsT/COVIA==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "dev": true + }, + "node_modules/isexe": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", + "integrity": "sha1-6PvzdNxVb/iUehDcsFctYz8s+hA=", + "dev": true + }, + "node_modules/isobject": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/isobject/-/isobject-3.0.1.tgz", + "integrity": "sha1-TkMekrEalzFjaqH5yNHMvP2reN8=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/json-stable-stringify": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/json-stable-stringify/-/json-stable-stringify-0.0.1.tgz", + "integrity": "sha1-YRwj6BTbN1Un34URk9tZ3Sryf0U=", + "dev": true, + "dependencies": { + "jsonify": "~0.0.0" + } + }, + "node_modules/jsonify": { + "version": "0.0.0", + "resolved": "https://registry.npmjs.org/jsonify/-/jsonify-0.0.0.tgz", + "integrity": "sha1-LHS27kHZPKUbe1qu6PUDYx0lKnM=", + "dev": true + }, + "node_modules/jsonparse": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/jsonparse/-/jsonparse-1.3.1.tgz", + "integrity": "sha1-P02uSpH6wxX3EGL4UhzCOfE2YoA=", + "dev": true, + "engines": [ + "node >= 0.2.0" + ] + }, + "node_modules/JSONStream": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/JSONStream/-/JSONStream-1.3.5.tgz", + "integrity": "sha512-E+iruNOY8VV9s4JEbe1aNEm6MiszPRr/UfcHMz0TQh1BXSxHK+ASV1R6W4HpjBhSeS+54PIsAMCBmwD06LLsqQ==", + "dev": true, + "dependencies": { + "jsonparse": "^1.2.0", + "through": ">=2.2.7 <3" + }, + "bin": { + "JSONStream": "bin.js" + }, + "engines": { + "node": "*" + } + }, + "node_modules/just-debounce": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/just-debounce/-/just-debounce-1.0.0.tgz", + "integrity": "sha1-h/zPrv/AtozRnVX2cilD+SnqNeo=", + "dev": true + }, + "node_modules/kind-of": { + "version": "6.0.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-6.0.2.tgz", + "integrity": "sha512-s5kLOcnH0XqDO+FvuaLX8DDjZ18CGFk7VygH40QoKPUQhW4e2rvM0rwUq0t8IQDOwYSeLK01U90OjzBTme2QqA==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/labeled-stream-splicer": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/labeled-stream-splicer/-/labeled-stream-splicer-2.0.1.tgz", + "integrity": "sha512-MC94mHZRvJ3LfykJlTUipBqenZz1pacOZEMhhQ8dMGcDHs0SBE5GbsavUXV7YtP3icBW17W0Zy1I0lfASmo9Pg==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "isarray": "^2.0.4", + "stream-splicer": "^2.0.0" + } + }, + "node_modules/labeled-stream-splicer/node_modules/isarray": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-2.0.4.tgz", + "integrity": "sha512-GMxXOiUirWg1xTKRipM0Ek07rX+ubx4nNVElTJdNLYmNO/2YrDkgJGw9CljXn+r4EWiDQg/8lsRdHyg2PJuUaA==", + "dev": true + }, + "node_modules/last-run": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/last-run/-/last-run-1.1.1.tgz", + "integrity": "sha1-RblpQsF7HHnHchmCWbqUO+v4yls=", + "dev": true, + "dependencies": { + "default-resolution": "^2.0.0", + "es6-weak-map": "^2.0.1" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/lazystream": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/lazystream/-/lazystream-1.0.0.tgz", + "integrity": "sha1-9plf4PggOS9hOWvolGJAe7dxaOQ=", + "dev": true, + "dependencies": { + "readable-stream": "^2.0.5" + }, + "engines": { + "node": ">= 0.6.3" + } + }, + "node_modules/lcid": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/lcid/-/lcid-1.0.0.tgz", + "integrity": "sha1-MIrMr6C8SDo4Z7S28rlQYlHRuDU=", + "dev": true, + "dependencies": { + "invert-kv": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/lead": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/lead/-/lead-1.0.0.tgz", + "integrity": "sha1-bxT5mje+Op3XhPVJVpDlkDRm7kI=", + "dev": true, + "dependencies": { + "flush-write-stream": "^1.0.2" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/liftoff": { + "version": "2.5.0", + "resolved": "https://registry.npmjs.org/liftoff/-/liftoff-2.5.0.tgz", + "integrity": "sha1-IAkpG7Mc6oYbvxCnwVooyvdcMew=", + "dev": true, + "dependencies": { + "extend": "^3.0.0", + "findup-sync": "^2.0.0", + "fined": "^1.0.1", + "flagged-respawn": "^1.0.0", + "is-plain-object": "^2.0.4", + "object.map": "^1.0.0", + "rechoir": "^0.6.2", + "resolve": "^1.1.7" + }, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/load-json-file": { + "version": "1.1.0", + "resolved": "http://registry.npmjs.org/load-json-file/-/load-json-file-1.1.0.tgz", + "integrity": "sha1-lWkFcI1YtLq0wiYbBPWfMcmTdMA=", + "dev": true, + "dependencies": { + "graceful-fs": "^4.1.2", + "parse-json": "^2.2.0", + "pify": "^2.0.0", + "pinkie-promise": "^2.0.0", + "strip-bom": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/lodash": { + "version": "4.17.11", + "resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.11.tgz", + "integrity": "sha512-cQKh8igo5QUhZ7lg38DYWAxMvjSAKG0A8wGSVimP07SIUEK2UO+arSRKbRZWtelMtN5V0Hkwh5ryOto/SshYIg==", + "dev": true + }, + "node_modules/lodash.debounce": { + "version": "4.0.8", + "resolved": "https://registry.npmjs.org/lodash.debounce/-/lodash.debounce-4.0.8.tgz", + "integrity": "sha1-gteb/zCmfEAF/9XiUVMArZyk168=", + "dev": true + }, + "node_modules/lodash.memoize": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/lodash.memoize/-/lodash.memoize-3.0.4.tgz", + "integrity": "sha1-LcvSwofLwKVcxCMovQxzYVDVPj8=", + "dev": true + }, + "node_modules/lru-queue": { + "version": "0.1.0", + "resolved": "https://registry.npmjs.org/lru-queue/-/lru-queue-0.1.0.tgz", + "integrity": "sha1-Jzi9nw089PhEkMVzbEhpmsYyzaM=", + "dev": true, + "dependencies": { + "es5-ext": "~0.10.2" + } + }, + "node_modules/make-error": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/make-error/-/make-error-1.3.5.tgz", + "integrity": "sha512-c3sIjNUow0+8swNwVpqoH4YCShKNFkMaw6oH1mNS2haDZQqkeZFlHS3dhoeEbKKmJB4vXpJucU6oH75aDYeE9g==", + "dev": true + }, + "node_modules/make-error-cause": { + "version": "1.2.2", + "resolved": "https://registry.npmjs.org/make-error-cause/-/make-error-cause-1.2.2.tgz", + "integrity": "sha1-3wOI/NCzeBbf8KX7gQiTl3fcvJ0=", + "dev": true, + "dependencies": { + "make-error": "^1.2.0" + } + }, + "node_modules/make-iterator": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/make-iterator/-/make-iterator-1.0.1.tgz", + "integrity": "sha512-pxiuXh0iVEq7VM7KMIhs5gxsfxCux2URptUQaXo4iZZJxBAzTPOLE2BumO5dbfVYq/hBJFBR/a1mFDmOx5AGmw==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/map-cache": { + "version": "0.2.2", + "resolved": "https://registry.npmjs.org/map-cache/-/map-cache-0.2.2.tgz", + "integrity": "sha1-wyq9C9ZSXZsFFkW7TyasXcmKDb8=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/map-visit": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/map-visit/-/map-visit-1.0.0.tgz", + "integrity": "sha1-7Nyo8TFE5mDxtb1B8S80edmN+48=", + "dev": true, + "dependencies": { + "object-visit": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/matchdep": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/matchdep/-/matchdep-2.0.0.tgz", + "integrity": "sha1-xvNINKDY28OzfCfui7yyfHd1WC4=", + "dev": true, + "dependencies": { + "findup-sync": "^2.0.0", + "micromatch": "^3.0.4", + "resolve": "^1.4.0", + "stack-trace": "0.0.10" + }, + "engines": { + "node": ">= 0.10.0" + } + }, + "node_modules/md5.js": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/md5.js/-/md5.js-1.3.5.tgz", + "integrity": "sha512-xitP+WxNPcTTOgnTJcrhM0xvdPepipPSf3I8EIpGKeFLjt3PlJLIDG3u8EX53ZIubkb+5U2+3rELYpEhHhzdkg==", + "dev": true, + "dependencies": { + "hash-base": "^3.0.0", + "inherits": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/md5.js/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/memoizee": { + "version": "0.4.14", + "resolved": "https://registry.npmjs.org/memoizee/-/memoizee-0.4.14.tgz", + "integrity": "sha512-/SWFvWegAIYAO4NQMpcX+gcra0yEZu4OntmUdrBaWrJncxOqAziGFlHxc7yjKVK2uu3lpPW27P27wkR82wA8mg==", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "^0.10.45", + "es6-weak-map": "^2.0.2", + "event-emitter": "^0.3.5", + "is-promise": "^2.1", + "lru-queue": "0.1", + "next-tick": "1", + "timers-ext": "^0.1.5" + } + }, + "node_modules/memoizee/node_modules/es5-ext": { + "version": "0.10.46", + "resolved": "https://registry.npmjs.org/es5-ext/-/es5-ext-0.10.46.tgz", + "integrity": "sha512-24XxRvJXNFwEMpJb3nOkiRJKRoupmjYmOPVlI65Qy2SrtxwOTB+g6ODjBKOtwEHbYrhWRty9xxOWLNdClT2djw==", + "dev": true, + "dependencies": { + "es6-iterator": "~2.0.3", + "es6-symbol": "~3.1.1", + "next-tick": "1" + } + }, + "node_modules/memoizee/node_modules/es6-iterator": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/es6-iterator/-/es6-iterator-2.0.3.tgz", + "integrity": "sha1-p96IkUGgWpSwhUQDstCg+/qY87c=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "^0.10.35", + "es6-symbol": "^3.1.1" + } + }, + "node_modules/micromatch": { + "version": "3.1.10", + "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-3.1.10.tgz", + "integrity": "sha512-MWikgl9n9M3w+bpsY3He8L+w9eF9338xRl8IAO5viDizwSzziFEyUzo2xrrloB64ADbTf8uA8vRqqttDTOmccg==", + "dev": true, + "dependencies": { + "arr-diff": "^4.0.0", + "array-unique": "^0.3.2", + "braces": "^2.3.1", + "define-property": "^2.0.2", + "extend-shallow": "^3.0.2", + "extglob": "^2.0.4", + "fragment-cache": "^0.2.1", + "kind-of": "^6.0.2", + "nanomatch": "^1.2.9", + "object.pick": "^1.3.0", + "regex-not": "^1.0.0", + "snapdragon": "^0.8.1", + "to-regex": "^3.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/miller-rabin": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/miller-rabin/-/miller-rabin-4.0.1.tgz", + "integrity": "sha512-115fLhvZVqWwHPbClyntxEVfVDfl9DLLTuJvq3g2O/Oxi8AiNouAHvDSzHS0viUJc+V5vm3eq91Xwqn9dp4jRA==", + "dev": true, + "dependencies": { + "bn.js": "^4.0.0", + "brorand": "^1.0.1" + }, + "bin": { + "miller-rabin": "bin/miller-rabin" + } + }, + "node_modules/minimalistic-assert": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/minimalistic-assert/-/minimalistic-assert-1.0.1.tgz", + "integrity": "sha512-UtJcAD4yEaGtjPezWuO9wC4nwUnVH/8/Im3yEHQP4b67cXlD/Qr9hdITCU1xDbSEXg2XKNaP8jsReV7vQd00/A==", + "dev": true + }, + "node_modules/minimalistic-crypto-utils": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/minimalistic-crypto-utils/-/minimalistic-crypto-utils-1.0.1.tgz", + "integrity": "sha1-9sAMHAsIIkblxNmd+4x8CDsrWCo=", + "dev": true + }, + "node_modules/minimatch": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", + "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", + "dev": true, + "dependencies": { + "brace-expansion": "^1.1.7" + }, + "engines": { + "node": "*" + } + }, + "node_modules/minimist": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.0.tgz", + "integrity": "sha1-o1AIsg9BOD7sH7kU9M1d95omQoQ=", + "dev": true + }, + "node_modules/mixin-deep": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/mixin-deep/-/mixin-deep-1.3.1.tgz", + "integrity": "sha512-8ZItLHeEgaqEvd5lYBXfm4EZSFCX29Jb9K+lAHhDKzReKBQKj3R+7NOF6tjqYi9t4oI8VUfaWITJQm86wnXGNQ==", + "dev": true, + "dependencies": { + "for-in": "^1.0.2", + "is-extendable": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/mixin-deep/node_modules/is-extendable": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/is-extendable/-/is-extendable-1.0.1.tgz", + "integrity": "sha512-arnXMxT1hhoKo9k1LZdmlNyJdDDfy2v0fXjFlmok4+i8ul/6WlbVge9bhM74OpNPQPMGUToDtz+KXa1PneJxOA==", + "dev": true, + "dependencies": { + "is-plain-object": "^2.0.4" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/module-deps": { + "version": "4.1.1", + "resolved": "https://registry.npmjs.org/module-deps/-/module-deps-4.1.1.tgz", + "integrity": "sha1-IyFYM/HaE/1gbMuAh7RIUty4If0=", + "dev": true, + "dependencies": { + "browser-resolve": "^1.7.0", + "cached-path-relative": "^1.0.0", + "concat-stream": "~1.5.0", + "defined": "^1.0.0", + "detective": "^4.0.0", + "duplexer2": "^0.1.2", + "inherits": "^2.0.1", + "JSONStream": "^1.0.3", + "parents": "^1.0.0", + "readable-stream": "^2.0.2", + "resolve": "^1.1.3", + "stream-combiner2": "^1.1.1", + "subarg": "^1.0.0", + "through2": "^2.0.0", + "xtend": "^4.0.0" + }, + "bin": { + "module-deps": "bin/cmd.js" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/mute-stdout": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/mute-stdout/-/mute-stdout-1.0.1.tgz", + "integrity": "sha512-kDcwXR4PS7caBpuRYYBUz9iVixUk3anO3f5OYFiIPwK/20vCzKCHyKoulbiDY1S53zD2bxUpxN/IJ+TnXjfvxg==", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/nan": { + "version": "2.11.1", + "resolved": "https://registry.npmjs.org/nan/-/nan-2.11.1.tgz", + "integrity": "sha512-iji6k87OSXa0CcrLl9z+ZiYSuR2o+c0bGuNmXdrhTQTakxytAFsC56SArGYoiHlJlFoHSnvmhpceZJaXkVuOtA==", + "dev": true, + "optional": true + }, + "node_modules/nanomatch": { + "version": "1.2.13", + "resolved": "https://registry.npmjs.org/nanomatch/-/nanomatch-1.2.13.tgz", + "integrity": "sha512-fpoe2T0RbHwBTBUOftAfBPaDEi06ufaUai0mE6Yn1kacc3SnTErfb/h+X94VXzI64rKFHYImXSvdwGGCmwOqCA==", + "dev": true, + "dependencies": { + "arr-diff": "^4.0.0", + "array-unique": "^0.3.2", + "define-property": "^2.0.2", + "extend-shallow": "^3.0.2", + "fragment-cache": "^0.2.1", + "is-windows": "^1.0.2", + "kind-of": "^6.0.2", + "object.pick": "^1.3.0", + "regex-not": "^1.0.0", + "snapdragon": "^0.8.1", + "to-regex": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/next-tick": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/next-tick/-/next-tick-1.0.0.tgz", + "integrity": "sha1-yobR/ogoFpsBICCOPchCS524NCw=", + "dev": true + }, + "node_modules/normalize-package-data": { + "version": "2.4.0", + "resolved": "https://registry.npmjs.org/normalize-package-data/-/normalize-package-data-2.4.0.tgz", + "integrity": "sha512-9jjUFbTPfEy3R/ad/2oNbKtW9Hgovl5O1FvFWKkKblNXoN/Oou6+9+KKohPK13Yc3/TyunyWhJp6gvRNR/PPAw==", + "dev": true, + "dependencies": { + "hosted-git-info": "^2.1.4", + "is-builtin-module": "^1.0.0", + "semver": "2 || 3 || 4 || 5", + "validate-npm-package-license": "^3.0.1" + } + }, + "node_modules/normalize-path": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/normalize-path/-/normalize-path-2.1.1.tgz", + "integrity": "sha1-GrKLVW4Zg2Oowab35vogE3/mrtk=", + "dev": true, + "dependencies": { + "remove-trailing-separator": "^1.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/now-and-later": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/now-and-later/-/now-and-later-2.0.0.tgz", + "integrity": "sha1-vGHLtFbXnLMiB85HygUTb/Ln1u4=", + "dev": true, + "dependencies": { + "once": "^1.3.2" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/number-is-nan": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/number-is-nan/-/number-is-nan-1.0.1.tgz", + "integrity": "sha1-CXtgK1NCKlIsGvuHkDGDNpQaAR0=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object-assign": { + "version": "4.1.1", + "resolved": "https://registry.npmjs.org/object-assign/-/object-assign-4.1.1.tgz", + "integrity": "sha1-IQmtx5ZYh8/AXLvUQsrIv7s2CGM=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object-copy": { + "version": "0.1.0", + "resolved": "https://registry.npmjs.org/object-copy/-/object-copy-0.1.0.tgz", + "integrity": "sha1-fn2Fi3gb18mRpBupde04EnVOmYw=", + "dev": true, + "dependencies": { + "copy-descriptor": "^0.1.0", + "define-property": "^0.2.5", + "kind-of": "^3.0.3" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object-copy/node_modules/define-property": { + "version": "0.2.5", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-0.2.5.tgz", + "integrity": "sha1-w1se+RjsPJkPmlvFe+BKrOxcgRY=", + "dev": true, + "dependencies": { + "is-descriptor": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object-copy/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object-keys": { + "version": "1.0.12", + "resolved": "https://registry.npmjs.org/object-keys/-/object-keys-1.0.12.tgz", + "integrity": "sha512-FTMyFUm2wBcGHnH2eXmz7tC6IwlqQZ6mVZ+6dm6vZ4IQIHjs6FdNsQBuKGPuUUUY6NfJw2PshC08Tn6LzLDOag==", + "dev": true, + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/object-visit": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/object-visit/-/object-visit-1.0.1.tgz", + "integrity": "sha1-95xEk68MU3e1n+OdOV5BBC3QRbs=", + "dev": true, + "dependencies": { + "isobject": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object.assign": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/object.assign/-/object.assign-4.1.0.tgz", + "integrity": "sha512-exHJeq6kBKj58mqGyTQ9DFvrZC/eR6OwxzoM9YRoGBqrXYonaFyGiFMuc9VZrXf7DarreEwMpurG3dd+CNyW5w==", + "dev": true, + "dependencies": { + "define-properties": "^1.1.2", + "function-bind": "^1.1.1", + "has-symbols": "^1.0.0", + "object-keys": "^1.0.11" + }, + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/object.defaults": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/object.defaults/-/object.defaults-1.1.0.tgz", + "integrity": "sha1-On+GgzS0B96gbaFtiNXNKeQ1/s8=", + "dev": true, + "dependencies": { + "array-each": "^1.0.1", + "array-slice": "^1.0.0", + "for-own": "^1.0.0", + "isobject": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object.map": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/object.map/-/object.map-1.0.1.tgz", + "integrity": "sha1-z4Plncj8wK1fQlDh94s7gb2AHTc=", + "dev": true, + "dependencies": { + "for-own": "^1.0.0", + "make-iterator": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object.pick": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/object.pick/-/object.pick-1.3.0.tgz", + "integrity": "sha1-h6EKxMFpS9Lhy/U1kaZhQftd10c=", + "dev": true, + "dependencies": { + "isobject": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/object.reduce": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/object.reduce/-/object.reduce-1.0.1.tgz", + "integrity": "sha1-b+NI8qx/oPlcpiEiZZkJaCW7A60=", + "dev": true, + "dependencies": { + "for-own": "^1.0.0", + "make-iterator": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/once": { + "version": "1.3.3", + "resolved": "https://registry.npmjs.org/once/-/once-1.3.3.tgz", + "integrity": "sha1-suJhVXzkwxTsgwTz+oJmPkKXyiA=", + "dev": true, + "dependencies": { + "wrappy": "1" + } + }, + "node_modules/ordered-read-streams": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/ordered-read-streams/-/ordered-read-streams-1.0.1.tgz", + "integrity": "sha1-d8DLN8QVJdZBZtmQ/61+xqDhNj4=", + "dev": true, + "dependencies": { + "readable-stream": "^2.0.1" + } + }, + "node_modules/os-browserify": { + "version": "0.3.0", + "resolved": "https://registry.npmjs.org/os-browserify/-/os-browserify-0.3.0.tgz", + "integrity": "sha1-hUNzx/XCMVkU/Jv8a9gjj92h7Cc=", + "dev": true + }, + "node_modules/os-locale": { + "version": "1.4.0", + "resolved": "http://registry.npmjs.org/os-locale/-/os-locale-1.4.0.tgz", + "integrity": "sha1-IPnxeuKe00XoveWDsT0gCYA8FNk=", + "dev": true, + "dependencies": { + "lcid": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/pako": { + "version": "1.0.6", + "resolved": "https://registry.npmjs.org/pako/-/pako-1.0.6.tgz", + "integrity": "sha512-lQe48YPsMJAig+yngZ87Lus+NF+3mtu7DVOBu6b/gHO1YpKwIj5AWjZ/TOS7i46HD/UixzWb1zeWDZfGZ3iYcg==", + "dev": true + }, + "node_modules/parents": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/parents/-/parents-1.0.1.tgz", + "integrity": "sha1-/t1NK/GTp3dF/nHjcdc8MwfZx1E=", + "dev": true, + "dependencies": { + "path-platform": "~0.11.15" + } + }, + "node_modules/parse-asn1": { + "version": "5.1.1", + "resolved": "http://registry.npmjs.org/parse-asn1/-/parse-asn1-5.1.1.tgz", + "integrity": "sha512-KPx7flKXg775zZpnp9SxJlz00gTd4BmJ2yJufSc44gMCRrRQ7NSzAcSJQfifuOLgW6bEi+ftrALtsgALeB2Adw==", + "dev": true, + "dependencies": { + "asn1.js": "^4.0.0", + "browserify-aes": "^1.0.0", + "create-hash": "^1.1.0", + "evp_bytestokey": "^1.0.0", + "pbkdf2": "^3.0.3" + } + }, + "node_modules/parse-filepath": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/parse-filepath/-/parse-filepath-1.0.2.tgz", + "integrity": "sha1-pjISf1Oq89FYdvWHLz/6x2PWyJE=", + "dev": true, + "dependencies": { + "is-absolute": "^1.0.0", + "map-cache": "^0.2.0", + "path-root": "^0.1.1" + }, + "engines": { + "node": ">=0.8" + } + }, + "node_modules/parse-json": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/parse-json/-/parse-json-2.2.0.tgz", + "integrity": "sha1-9ID0BDTvgHQfhGkJn43qGPVaTck=", + "dev": true, + "dependencies": { + "error-ex": "^1.2.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/parse-passwd": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/parse-passwd/-/parse-passwd-1.0.0.tgz", + "integrity": "sha1-bVuTSkVpk7I9N/QKOC1vFmao5cY=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/pascalcase": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/pascalcase/-/pascalcase-0.1.1.tgz", + "integrity": "sha1-s2PlXoAGym/iF4TS2yK9FdeRfxQ=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-browserify": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/path-browserify/-/path-browserify-0.0.1.tgz", + "integrity": "sha512-BapA40NHICOS+USX9SN4tyhq+A2RrN/Ws5F0Z5aMHDp98Fl86lX8Oti8B7uN93L4Ifv4fHOEA+pQw87gmMO/lQ==", + "dev": true + }, + "node_modules/path-dirname": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/path-dirname/-/path-dirname-1.0.2.tgz", + "integrity": "sha1-zDPSTVJeCZpTiMAzbG4yuRYGCeA=", + "dev": true + }, + "node_modules/path-exists": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/path-exists/-/path-exists-2.1.0.tgz", + "integrity": "sha1-D+tsZPD8UY2adU3V77YscCJ2H0s=", + "dev": true, + "dependencies": { + "pinkie-promise": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-is-absolute": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", + "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-parse": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/path-parse/-/path-parse-1.0.5.tgz", + "integrity": "sha1-PBrfhx6pzWyUMbbqK9dKD/BVxME=", + "dev": true + }, + "node_modules/path-platform": { + "version": "0.11.15", + "resolved": "https://registry.npmjs.org/path-platform/-/path-platform-0.11.15.tgz", + "integrity": "sha1-6GQhf3TDaFDwhSt43Hv31KVyG/I=", + "dev": true, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/path-root": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/path-root/-/path-root-0.1.1.tgz", + "integrity": "sha1-mkpoFMrBwM1zNgqV8yCDyOpHRbc=", + "dev": true, + "dependencies": { + "path-root-regex": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-root-regex": { + "version": "0.1.2", + "resolved": "https://registry.npmjs.org/path-root-regex/-/path-root-regex-0.1.2.tgz", + "integrity": "sha1-v8zcjfWxLcUsi0PsONGNcsBLqW0=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-type": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/path-type/-/path-type-1.1.0.tgz", + "integrity": "sha1-WcRPfuSR2nBNpBXaWkBwuk+P5EE=", + "dev": true, + "dependencies": { + "graceful-fs": "^4.1.2", + "pify": "^2.0.0", + "pinkie-promise": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/pbkdf2": { + "version": "3.0.17", + "resolved": "https://registry.npmjs.org/pbkdf2/-/pbkdf2-3.0.17.tgz", + "integrity": "sha512-U/il5MsrZp7mGg3mSQfn742na2T+1/vHDCG5/iTI3X9MKUuYUZVLQhyRsg06mCgDBTd57TxzgZt7P+fYfjRLtA==", + "dev": true, + "dependencies": { + "create-hash": "^1.1.2", + "create-hmac": "^1.1.4", + "ripemd160": "^2.0.1", + "safe-buffer": "^5.0.1", + "sha.js": "^2.4.8" + }, + "engines": { + "node": ">=0.12" + } + }, + "node_modules/pify": { + "version": "2.3.0", + "resolved": "http://registry.npmjs.org/pify/-/pify-2.3.0.tgz", + "integrity": "sha1-7RQaasBDqEnqWISY59yosVMw6Qw=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/pinkie": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/pinkie/-/pinkie-2.0.4.tgz", + "integrity": "sha1-clVrgM+g1IqXToDnckjoDtT3+HA=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/pinkie-promise": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/pinkie-promise/-/pinkie-promise-2.0.1.tgz", + "integrity": "sha1-ITXW36ejWMBprJsXh3YogihFD/o=", + "dev": true, + "dependencies": { + "pinkie": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/posix-character-classes": { + "version": "0.1.1", + "resolved": "https://registry.npmjs.org/posix-character-classes/-/posix-character-classes-0.1.1.tgz", + "integrity": "sha1-AerA/jta9xoqbAL+q7jB/vfgDqs=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/preact": { + "version": "8.3.1", + "resolved": "https://registry.npmjs.org/preact/-/preact-8.3.1.tgz", + "integrity": "sha512-s8H1Y8O9e+mOBo3UP1jvWqArPmjCba2lrrGLlq/0kN1XuIINUbYtf97iiXKxCuG3eYwmppPKnyW2DBrNj/TuTg==", + "hasInstallScript": true + }, + "node_modules/pretty-hrtime": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/pretty-hrtime/-/pretty-hrtime-1.0.3.tgz", + "integrity": "sha1-t+PqQkNaTJsnWdmeDyAesZWALuE=", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/process": { + "version": "0.11.10", + "resolved": "https://registry.npmjs.org/process/-/process-0.11.10.tgz", + "integrity": "sha1-czIwDoQBYb2j5podHZGn1LwW8YI=", + "dev": true, + "engines": { + "node": ">= 0.6.0" + } + }, + "node_modules/process-nextick-args": { + "version": "1.0.7", + "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-1.0.7.tgz", + "integrity": "sha1-FQ4gt1ZZCtP5EJPyWk8q2L/zC6M=", + "dev": true + }, + "node_modules/public-encrypt": { + "version": "4.0.3", + "resolved": "https://registry.npmjs.org/public-encrypt/-/public-encrypt-4.0.3.tgz", + "integrity": "sha512-zVpa8oKZSz5bTMTFClc1fQOnyyEzpl5ozpi1B5YcvBrdohMjH2rfsBtyXcuNuwjsDIXmBYlF2N5FlJYhR29t8Q==", + "dev": true, + "dependencies": { + "bn.js": "^4.1.0", + "browserify-rsa": "^4.0.0", + "create-hash": "^1.1.0", + "parse-asn1": "^5.0.0", + "randombytes": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/public-encrypt/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/pump": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/pump/-/pump-2.0.1.tgz", + "integrity": "sha512-ruPMNRkN3MHP1cWJc9OWr+T/xDP0jhXYCLfJcBuX54hhfIBnaQmAUMfDcG4DM5UMWByBbJY69QSphm3jtDKIkA==", + "dev": true, + "dependencies": { + "end-of-stream": "^1.1.0", + "once": "^1.3.1" + } + }, + "node_modules/pumpify": { + "version": "1.5.1", + "resolved": "https://registry.npmjs.org/pumpify/-/pumpify-1.5.1.tgz", + "integrity": "sha512-oClZI37HvuUJJxSKKrC17bZ9Cu0ZYhEAGPsPUy9KlMUmv9dKX2o77RUmq7f3XjIxbwyGwYzbzQ1L2Ks8sIradQ==", + "dev": true, + "dependencies": { + "duplexify": "^3.6.0", + "inherits": "^2.0.3", + "pump": "^2.0.0" + } + }, + "node_modules/punycode": { + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.4.1.tgz", + "integrity": "sha1-wNWmOycYgArY4esPpSachN1BhF4=", + "dev": true + }, + "node_modules/querystring": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/querystring/-/querystring-0.2.0.tgz", + "integrity": "sha1-sgmEkgO7Jd+CDadW50cAWHhSFiA=", + "dev": true, + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/querystring-es3": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/querystring-es3/-/querystring-es3-0.2.1.tgz", + "integrity": "sha1-nsYfeQSYdXB9aUFFlv2Qek1xHnM=", + "dev": true, + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/randombytes": { + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/randombytes/-/randombytes-2.0.6.tgz", + "integrity": "sha512-CIQ5OFxf4Jou6uOKe9t1AOgqpeU5fd70A8NPdHSGeYXqXsPe6peOwI0cUl88RWZ6sP1vPMV3avd/R6cZ5/sP1A==", + "dev": true, + "dependencies": { + "safe-buffer": "^5.1.0" + } + }, + "node_modules/randomfill": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/randomfill/-/randomfill-1.0.4.tgz", + "integrity": "sha512-87lcbR8+MhcWcUiQ+9e+Rwx8MyR2P7qnt15ynUlbm3TU/fjbgz4GsvfSUDTemtCCtVCqb4ZcEFlyPNTh9bBTLw==", + "dev": true, + "dependencies": { + "randombytes": "^2.0.5", + "safe-buffer": "^5.1.0" + } + }, + "node_modules/read-only-stream": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/read-only-stream/-/read-only-stream-2.0.0.tgz", + "integrity": "sha1-JyT9aoET1zdkrCiNQ4YnDB2/F/A=", + "dev": true, + "dependencies": { + "readable-stream": "^2.0.2" + } + }, + "node_modules/read-pkg": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/read-pkg/-/read-pkg-1.1.0.tgz", + "integrity": "sha1-9f+qXs0pyzHAR0vKfXVra7KePyg=", + "dev": true, + "dependencies": { + "load-json-file": "^1.0.0", + "normalize-package-data": "^2.3.2", + "path-type": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/read-pkg-up": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/read-pkg-up/-/read-pkg-up-1.0.1.tgz", + "integrity": "sha1-nWPBMnbAZZGNV/ACpX9AobZD+wI=", + "dev": true, + "dependencies": { + "find-up": "^1.0.0", + "read-pkg": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/readable-stream": { + "version": "2.3.6", + "resolved": "http://registry.npmjs.org/readable-stream/-/readable-stream-2.3.6.tgz", + "integrity": "sha512-tQtKA9WIAhBF3+VLAseyMqZeBjW0AHJoxOtYqSUZNJxauErmLbVm2FW1y+J/YA9dUrAC39ITejlZWhVIwawkKw==", + "dev": true, + "dependencies": { + "core-util-is": "~1.0.0", + "inherits": "~2.0.3", + "isarray": "~1.0.0", + "process-nextick-args": "~2.0.0", + "safe-buffer": "~5.1.1", + "string_decoder": "~1.1.1", + "util-deprecate": "~1.0.1" + } + }, + "node_modules/readable-stream/node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "dev": true + }, + "node_modules/readable-stream/node_modules/process-nextick-args": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.0.tgz", + "integrity": "sha512-MtEC1TqN0EU5nephaJ4rAtThHtC86dNN9qCuEhtshvpVBkAW5ZO7BASN9REnF9eoXGcRub+pFuKEpOHE+HbEMw==", + "dev": true + }, + "node_modules/readable-stream/node_modules/string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "dev": true, + "dependencies": { + "safe-buffer": "~5.1.0" + } + }, + "node_modules/readdirp": { + "version": "2.2.1", + "resolved": "https://registry.npmjs.org/readdirp/-/readdirp-2.2.1.tgz", + "integrity": "sha512-1JU/8q+VgFZyxwrJ+SVIOsh+KywWGpds3NTqikiKpDMZWScmAYyKIgqkO+ARvNWJfXeXR1zxz7aHF4u4CyH6vQ==", + "dev": true, + "dependencies": { + "graceful-fs": "^4.1.11", + "micromatch": "^3.1.10", + "readable-stream": "^2.0.2" + }, + "engines": { + "node": ">=0.10" + } + }, + "node_modules/rechoir": { + "version": "0.6.2", + "resolved": "https://registry.npmjs.org/rechoir/-/rechoir-0.6.2.tgz", + "integrity": "sha1-hSBLVNuoLVdC4oyWdW70OvUOM4Q=", + "dev": true, + "dependencies": { + "resolve": "^1.1.6" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/regex-not": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/regex-not/-/regex-not-1.0.2.tgz", + "integrity": "sha512-J6SDjUgDxQj5NusnOtdFxDwN/+HWykR8GELwctJ7mdqhcyy1xEc4SRFHUXvxTp661YaVKAjfRLZ9cCqS6tn32A==", + "dev": true, + "dependencies": { + "extend-shallow": "^3.0.2", + "safe-regex": "^1.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/remove-bom-buffer": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/remove-bom-buffer/-/remove-bom-buffer-3.0.0.tgz", + "integrity": "sha512-8v2rWhaakv18qcvNeli2mZ/TMTL2nEyAKRvzo1WtnZBl15SHyEhrCu2/xKlJyUFKHiHgfXIyuY6g2dObJJycXQ==", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5", + "is-utf8": "^0.2.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/remove-bom-stream": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/remove-bom-stream/-/remove-bom-stream-1.2.0.tgz", + "integrity": "sha1-BfGlk/FuQuH7kOv1nejlaVJflSM=", + "dev": true, + "dependencies": { + "remove-bom-buffer": "^3.0.0", + "safe-buffer": "^5.1.0", + "through2": "^2.0.3" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/remove-trailing-separator": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/remove-trailing-separator/-/remove-trailing-separator-1.1.0.tgz", + "integrity": "sha1-wkvOKig62tW8P1jg1IJJuSN52O8=", + "dev": true + }, + "node_modules/repeat-element": { + "version": "1.1.3", + "resolved": "https://registry.npmjs.org/repeat-element/-/repeat-element-1.1.3.tgz", + "integrity": "sha512-ahGq0ZnV5m5XtZLMb+vP76kcAM5nkLqk0lpqAuojSKGgQtn4eRi4ZZGm2olo2zKFH+sMsWaqOCW1dqAnOru72g==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/repeat-string": { + "version": "1.6.1", + "resolved": "https://registry.npmjs.org/repeat-string/-/repeat-string-1.6.1.tgz", + "integrity": "sha1-jcrkcOHIirwtYA//Sndihtp15jc=", + "dev": true, + "engines": { + "node": ">=0.10" + } + }, + "node_modules/replace-homedir": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/replace-homedir/-/replace-homedir-1.0.0.tgz", + "integrity": "sha1-6H9tUTuSjd6AgmDBK+f+xv9ueYw=", + "dev": true, + "dependencies": { + "homedir-polyfill": "^1.0.1", + "is-absolute": "^1.0.0", + "remove-trailing-separator": "^1.1.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/require-directory": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/require-directory/-/require-directory-2.1.1.tgz", + "integrity": "sha1-jGStX9MNqxyXbiNE/+f3kqam30I=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/require-main-filename": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/require-main-filename/-/require-main-filename-1.0.1.tgz", + "integrity": "sha1-l/cXtp1IeE9fUmpsWqj/3aBVpNE=", + "dev": true + }, + "node_modules/resolve": { + "version": "1.4.0", + "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.4.0.tgz", + "integrity": "sha512-aW7sVKPufyHqOmyyLzg/J+8606v5nevBgaliIlV7nUpVMsDnoBGV/cbSLNjZAg9q0Cfd/+easKVKQ8vOu8fn1Q==", + "dev": true, + "dependencies": { + "path-parse": "^1.0.5" + } + }, + "node_modules/resolve-dir": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/resolve-dir/-/resolve-dir-1.0.1.tgz", + "integrity": "sha1-eaQGRMNivoLybv/nOcm7U4IEb0M=", + "dev": true, + "dependencies": { + "expand-tilde": "^2.0.0", + "global-modules": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/resolve-options": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/resolve-options/-/resolve-options-1.1.0.tgz", + "integrity": "sha1-MrueOcBtZzONyTeMDW1gdFZq0TE=", + "dev": true, + "dependencies": { + "value-or-function": "^3.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/resolve-url": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/resolve-url/-/resolve-url-0.2.1.tgz", + "integrity": "sha1-LGN/53yJOv0qZj/iGqkIAGjiBSo=", + "dev": true + }, + "node_modules/ret": { + "version": "0.1.15", + "resolved": "https://registry.npmjs.org/ret/-/ret-0.1.15.tgz", + "integrity": "sha512-TTlYpa+OL+vMMNG24xSlQGEJ3B/RzEfUlLct7b5G/ytav+wPrplCpVMFuwzXbkecJrb6IYo1iFb0S9v37754mg==", + "dev": true, + "engines": { + "node": ">=0.12" + } + }, + "node_modules/ripemd160": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/ripemd160/-/ripemd160-2.0.2.tgz", + "integrity": "sha512-ii4iagi25WusVoiC4B4lq7pbXfAp3D9v5CwfkY33vffw2+pkDjY1D8GaN7spsxvCSx8dkPqOZCEZyfxcmJG2IA==", + "dev": true, + "dependencies": { + "hash-base": "^3.0.0", + "inherits": "^2.0.1" + } + }, + "node_modules/safe-buffer": { + "version": "5.1.1", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.1.tgz", + "integrity": "sha512-kKvNJn6Mm93gAczWVJg7wH+wGYWNrDHdWvpUmHyEsgCtIwwo3bqPtV4tR5tuPaUhTOo/kvhVwd8XwwOllGYkbg==", + "dev": true + }, + "node_modules/safe-regex": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/safe-regex/-/safe-regex-1.1.0.tgz", + "integrity": "sha1-QKNmnzsHfR6UPURinhV91IAjvy4=", + "dev": true, + "dependencies": { + "ret": "~0.1.10" + } + }, + "node_modules/semver": { + "version": "5.6.0", + "resolved": "https://registry.npmjs.org/semver/-/semver-5.6.0.tgz", + "integrity": "sha512-RS9R6R35NYgQn++fkDWaOmqGoj4Ek9gGs+DPxNUZKuwE183xjJroKvyo1IzVFeXvUrvmALy6FWD5xrdJT25gMg==", + "dev": true, + "bin": { + "semver": "bin/semver" + } + }, + "node_modules/semver-greatest-satisfied-range": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/semver-greatest-satisfied-range/-/semver-greatest-satisfied-range-1.1.0.tgz", + "integrity": "sha1-E+jCZYq5aRywzXEJMkAoDTb3els=", + "dev": true, + "dependencies": { + "sver-compat": "^1.5.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/set-blocking": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/set-blocking/-/set-blocking-2.0.0.tgz", + "integrity": "sha1-BF+XgtARrppoA93TgrJDkrPYkPc=", + "dev": true + }, + "node_modules/set-value": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/set-value/-/set-value-2.0.0.tgz", + "integrity": "sha512-hw0yxk9GT/Hr5yJEYnHNKYXkIA8mVJgd9ditYZCe16ZczcaELYYcfvaXesNACk2O8O0nTiPQcQhGUQj8JLzeeg==", + "dev": true, + "dependencies": { + "extend-shallow": "^2.0.1", + "is-extendable": "^0.1.1", + "is-plain-object": "^2.0.3", + "split-string": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/set-value/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/sha.js": { + "version": "2.4.11", + "resolved": "http://registry.npmjs.org/sha.js/-/sha.js-2.4.11.tgz", + "integrity": "sha512-QMEp5B7cftE7APOjk5Y6xgrbWu+WkLVQwk8JNjZ8nKRciZaByEW6MubieAiToS7+dwvrjGhH8jRXz3MVd0AYqQ==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + }, + "bin": { + "sha.js": "bin.js" + } + }, + "node_modules/shasum": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/shasum/-/shasum-1.0.2.tgz", + "integrity": "sha1-5wEjENj0F/TetXEhUOVni4euVl8=", + "dev": true, + "dependencies": { + "json-stable-stringify": "~0.0.0", + "sha.js": "~2.4.4" + } + }, + "node_modules/shell-quote": { + "version": "1.6.1", + "resolved": "https://registry.npmjs.org/shell-quote/-/shell-quote-1.6.1.tgz", + "integrity": "sha1-9HgZSczkAmlxJ0MOo7PFR29IF2c=", + "dev": true, + "dependencies": { + "array-filter": "~0.0.0", + "array-map": "~0.0.0", + "array-reduce": "~0.0.0", + "jsonify": "~0.0.0" + } + }, + "node_modules/simple-concat": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/simple-concat/-/simple-concat-1.0.0.tgz", + "integrity": "sha1-c0TLuLbib7J9ZrL8hvn21Zl1IcY=", + "dev": true + }, + "node_modules/snapdragon": { + "version": "0.8.2", + "resolved": "https://registry.npmjs.org/snapdragon/-/snapdragon-0.8.2.tgz", + "integrity": "sha512-FtyOnWN/wCHTVXOMwvSv26d+ko5vWlIDD6zoUJ7LW8vh+ZBC8QdljveRP+crNrtBwioEUWy/4dMtbBjA4ioNlg==", + "dev": true, + "dependencies": { + "base": "^0.11.1", + "debug": "^2.2.0", + "define-property": "^0.2.5", + "extend-shallow": "^2.0.1", + "map-cache": "^0.2.2", + "source-map": "^0.5.6", + "source-map-resolve": "^0.5.0", + "use": "^3.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-node": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/snapdragon-node/-/snapdragon-node-2.1.1.tgz", + "integrity": "sha512-O27l4xaMYt/RSQ5TR3vpWCAB5Kb/czIcqUFOM/C4fYcLnbZUc1PkjTAMjof2pBWaSTwOUd6qUHcFGVGj7aIwnw==", + "dev": true, + "dependencies": { + "define-property": "^1.0.0", + "isobject": "^3.0.0", + "snapdragon-util": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-node/node_modules/define-property": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-1.0.0.tgz", + "integrity": "sha1-dp66rz9KY6rTr56NMEybvnm/sOY=", + "dev": true, + "dependencies": { + "is-descriptor": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-node/node_modules/is-accessor-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-accessor-descriptor/-/is-accessor-descriptor-1.0.0.tgz", + "integrity": "sha512-m5hnHTkcVsPfqx3AKlyttIPb7J+XykHvJP2B9bZDjlhLIoEq4XoK64Vg7boZlVWYK6LUY94dYPEE7Lh0ZkZKcQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-node/node_modules/is-data-descriptor": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-data-descriptor/-/is-data-descriptor-1.0.0.tgz", + "integrity": "sha512-jbRXy1FmtAoCjQkVmIVYwuuqDFUbaOeDjmed1tOGPrsMhtJA4rD9tkgA0F1qJ3gRFRXcHYVkdeaP50Q5rE/jLQ==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-node/node_modules/is-descriptor": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-descriptor/-/is-descriptor-1.0.2.tgz", + "integrity": "sha512-2eis5WqQGV7peooDyLmNEPUrps9+SXX5c9pL3xEB+4e9HnGuDa7mB7kHxHw4CbqS9k1T2hOH3miL8n8WtiYVtg==", + "dev": true, + "dependencies": { + "is-accessor-descriptor": "^1.0.0", + "is-data-descriptor": "^1.0.0", + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-util": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/snapdragon-util/-/snapdragon-util-3.0.1.tgz", + "integrity": "sha512-mbKkMdQKsjX4BAL4bRYTj21edOf8cN7XHdYUJEe+Zn99hVEYcMvKPct1IqNe7+AZPirn8BCDOQBHQZknqmKlZQ==", + "dev": true, + "dependencies": { + "kind-of": "^3.2.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon-util/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon/node_modules/atob": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/atob/-/atob-2.1.2.tgz", + "integrity": "sha512-Wm6ukoaOGJi/73p/cl2GvLjTI5JM1k/O14isD73YML8StrH/7/lRFgmg8nICZgD3bZZvjwCGxtMOD3wWNAu8cg==", + "dev": true, + "bin": { + "atob": "bin/atob.js" + }, + "engines": { + "node": ">= 4.5.0" + } + }, + "node_modules/snapdragon/node_modules/define-property": { + "version": "0.2.5", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-0.2.5.tgz", + "integrity": "sha1-w1se+RjsPJkPmlvFe+BKrOxcgRY=", + "dev": true, + "dependencies": { + "is-descriptor": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/snapdragon/node_modules/source-map-resolve": { + "version": "0.5.2", + "resolved": "https://registry.npmjs.org/source-map-resolve/-/source-map-resolve-0.5.2.tgz", + "integrity": "sha512-MjqsvNwyz1s0k81Goz/9vRBe9SZdB09Bdw+/zYyO+3CuPk6fouTaxscHkgtE8jKvf01kVfl8riHzERQ/kefaSA==", + "dev": true, + "dependencies": { + "atob": "^2.1.1", + "decode-uri-component": "^0.2.0", + "resolve-url": "^0.2.1", + "source-map-url": "^0.4.0", + "urix": "^0.1.0" + } + }, + "node_modules/snapdragon/node_modules/source-map-url": { + "version": "0.4.0", + "resolved": "https://registry.npmjs.org/source-map-url/-/source-map-url-0.4.0.tgz", + "integrity": "sha1-PpNdfd1zYxuXZZlW1VEo6HtQhKM=", + "dev": true + }, + "node_modules/source-map": { + "version": "0.5.7", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.5.7.tgz", + "integrity": "sha1-igOdLRAh0i0eoUyA2OpGi6LvP8w=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/source-map-resolve": { + "version": "0.5.2", + "resolved": "https://registry.npmjs.org/source-map-resolve/-/source-map-resolve-0.5.2.tgz", + "integrity": "sha512-MjqsvNwyz1s0k81Goz/9vRBe9SZdB09Bdw+/zYyO+3CuPk6fouTaxscHkgtE8jKvf01kVfl8riHzERQ/kefaSA==", + "dev": true, + "dependencies": { + "atob": "^2.1.1", + "decode-uri-component": "^0.2.0", + "resolve-url": "^0.2.1", + "source-map-url": "^0.4.0", + "urix": "^0.1.0" + } + }, + "node_modules/source-map-url": { + "version": "0.4.0", + "resolved": "https://registry.npmjs.org/source-map-url/-/source-map-url-0.4.0.tgz", + "integrity": "sha1-PpNdfd1zYxuXZZlW1VEo6HtQhKM=", + "dev": true + }, + "node_modules/sparkles": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/sparkles/-/sparkles-1.0.0.tgz", + "integrity": "sha1-Gsu/tZJDbRC76PeFt8xvgoFQEsM=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/spdx-correct": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/spdx-correct/-/spdx-correct-3.0.2.tgz", + "integrity": "sha512-q9hedtzyXHr5S0A1vEPoK/7l8NpfkFYTq6iCY+Pno2ZbdZR6WexZFtqeVGkGxW3TEJMN914Z55EnAGMmenlIQQ==", + "dev": true, + "dependencies": { + "spdx-expression-parse": "^3.0.0", + "spdx-license-ids": "^3.0.0" + } + }, + "node_modules/spdx-exceptions": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/spdx-exceptions/-/spdx-exceptions-2.2.0.tgz", + "integrity": "sha512-2XQACfElKi9SlVb1CYadKDXvoajPgBVPn/gOQLrTvHdElaVhr7ZEbqJaRnJLVNeaI4cMEAgVCeBMKF6MWRDCRA==", + "dev": true + }, + "node_modules/spdx-expression-parse": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/spdx-expression-parse/-/spdx-expression-parse-3.0.0.tgz", + "integrity": "sha512-Yg6D3XpRD4kkOmTpdgbUiEJFKghJH03fiC1OPll5h/0sO6neh2jqRDVHOQ4o/LMea0tgCkbMgea5ip/e+MkWyg==", + "dev": true, + "dependencies": { + "spdx-exceptions": "^2.1.0", + "spdx-license-ids": "^3.0.0" + } + }, + "node_modules/spdx-license-ids": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/spdx-license-ids/-/spdx-license-ids-3.0.1.tgz", + "integrity": "sha512-TfOfPcYGBB5sDuPn3deByxPhmfegAhpDYKSOXZQN81Oyrrif8ZCodOLzK3AesELnCx03kikhyDwh0pfvvQvF8w==", + "dev": true + }, + "node_modules/split-string": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/split-string/-/split-string-3.1.0.tgz", + "integrity": "sha512-NzNVhJDYpwceVVii8/Hu6DKfD2G+NrQHlS/V/qgv763EYudVwEcMQNxd2lh+0VrUByXN/oJkl5grOhYWvQUYiw==", + "dev": true, + "dependencies": { + "extend-shallow": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/stack-trace": { + "version": "0.0.10", + "resolved": "https://registry.npmjs.org/stack-trace/-/stack-trace-0.0.10.tgz", + "integrity": "sha1-VHxws0fo0ytOEI6hoqFZ5f3eGcA=", + "dev": true, + "engines": { + "node": "*" + } + }, + "node_modules/static-extend": { + "version": "0.1.2", + "resolved": "https://registry.npmjs.org/static-extend/-/static-extend-0.1.2.tgz", + "integrity": "sha1-YICcOcv/VTNyJv1eC1IPNB8ftcY=", + "dev": true, + "dependencies": { + "define-property": "^0.2.5", + "object-copy": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/static-extend/node_modules/define-property": { + "version": "0.2.5", + "resolved": "https://registry.npmjs.org/define-property/-/define-property-0.2.5.tgz", + "integrity": "sha1-w1se+RjsPJkPmlvFe+BKrOxcgRY=", + "dev": true, + "dependencies": { + "is-descriptor": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/stream-browserify": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/stream-browserify/-/stream-browserify-2.0.1.tgz", + "integrity": "sha1-ZiZu5fm9uZQKTkUUyvtDu3Hlyds=", + "dev": true, + "dependencies": { + "inherits": "~2.0.1", + "readable-stream": "^2.0.2" + } + }, + "node_modules/stream-combiner2": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/stream-combiner2/-/stream-combiner2-1.1.1.tgz", + "integrity": "sha1-+02KFCDqNidk4hrUeAOXvry0HL4=", + "dev": true, + "dependencies": { + "duplexer2": "~0.1.0", + "readable-stream": "^2.0.2" + } + }, + "node_modules/stream-exhaust": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/stream-exhaust/-/stream-exhaust-1.0.2.tgz", + "integrity": "sha512-b/qaq/GlBK5xaq1yrK9/zFcyRSTNxmcZwFLGSTG0mXgZl/4Z6GgiyYOXOvY7N3eEvFRAG1bkDRz5EPGSvPYQlw==", + "dev": true + }, + "node_modules/stream-http": { + "version": "2.8.3", + "resolved": "https://registry.npmjs.org/stream-http/-/stream-http-2.8.3.tgz", + "integrity": "sha512-+TSkfINHDo4J+ZobQLWiMouQYB+UVYFttRA94FpEzzJ7ZdqcL4uUUQ7WkdkI4DSozGmgBUE/a47L+38PenXhUw==", + "dev": true, + "dependencies": { + "builtin-status-codes": "^3.0.0", + "inherits": "^2.0.1", + "readable-stream": "^2.3.6", + "to-arraybuffer": "^1.0.0", + "xtend": "^4.0.0" + } + }, + "node_modules/stream-shift": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/stream-shift/-/stream-shift-1.0.0.tgz", + "integrity": "sha1-1cdSgl5TZ+eG944Y5EXqIjoVWVI=", + "dev": true + }, + "node_modules/stream-splicer": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/stream-splicer/-/stream-splicer-2.0.0.tgz", + "integrity": "sha1-G2O+Q4oTPktnHMGTUZdgAXWRDYM=", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "readable-stream": "^2.0.2" + } + }, + "node_modules/string_decoder": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.0.3.tgz", + "integrity": "sha512-4AH6Z5fzNNBcH+6XDMfA/BTt87skxqJlO0lAh3Dker5zThcAxG6mKz+iGu308UKoPPQ8Dcqx/4JhujzltRa+hQ==", + "dev": true, + "dependencies": { + "safe-buffer": "~5.1.0" + } + }, + "node_modules/string-width": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/string-width/-/string-width-1.0.2.tgz", + "integrity": "sha1-EYvfW4zcUaKn5w0hHgfisLmxB9M=", + "dev": true, + "dependencies": { + "code-point-at": "^1.0.0", + "is-fullwidth-code-point": "^1.0.0", + "strip-ansi": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/strip-ansi": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-3.0.1.tgz", + "integrity": "sha1-ajhfuIU9lS1f8F0Oiq+UJ43GPc8=", + "dev": true, + "dependencies": { + "ansi-regex": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/strip-bom": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/strip-bom/-/strip-bom-2.0.0.tgz", + "integrity": "sha1-YhmoVhZSBJHzV4i9vxRHqZx+aw4=", + "dev": true, + "dependencies": { + "is-utf8": "^0.2.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/strip-bom-string": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/strip-bom-string/-/strip-bom-string-1.0.0.tgz", + "integrity": "sha1-5SEekiQ2n7uB1jOi8ABE3IztrZI=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/strip-json-comments": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/strip-json-comments/-/strip-json-comments-2.0.1.tgz", + "integrity": "sha1-PFMZQukIwml8DsNEhYwobHygpgo=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/subarg": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/subarg/-/subarg-1.0.0.tgz", + "integrity": "sha1-9izxdYHplrSPyWVpn1TAauJouNI=", + "dev": true, + "dependencies": { + "minimist": "^1.1.0" + } + }, + "node_modules/sver-compat": { + "version": "1.5.0", + "resolved": "https://registry.npmjs.org/sver-compat/-/sver-compat-1.5.0.tgz", + "integrity": "sha1-PPh9/rTQe0o/FIJ7wYaz/QxkXNg=", + "dev": true, + "dependencies": { + "es6-iterator": "^2.0.1", + "es6-symbol": "^3.1.1" + } + }, + "node_modules/syntax-error": { + "version": "1.4.0", + "resolved": "https://registry.npmjs.org/syntax-error/-/syntax-error-1.4.0.tgz", + "integrity": "sha512-YPPlu67mdnHGTup2A8ff7BC2Pjq0e0Yp/IyTFN03zWO0RcK07uLcbi7C2KpGR2FvWbaB0+bfE27a+sBKebSo7w==", + "dev": true, + "dependencies": { + "acorn-node": "^1.2.0" + } + }, + "node_modules/through": { + "version": "2.3.8", + "resolved": "https://registry.npmjs.org/through/-/through-2.3.8.tgz", + "integrity": "sha1-DdTJ/6q8NXlgsbckEV1+Doai4fU=", + "dev": true + }, + "node_modules/through2": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/through2/-/through2-2.0.3.tgz", + "integrity": "sha1-AARWmzfHx0ujnEPzzteNGtlBQL4=", + "dev": true, + "dependencies": { + "readable-stream": "^2.1.5", + "xtend": "~4.0.1" + } + }, + "node_modules/through2-filter": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/through2-filter/-/through2-filter-2.0.0.tgz", + "integrity": "sha1-YLxVoNrLdghdsfna6Zq0P4PWIuw=", + "dev": true, + "dependencies": { + "through2": "~2.0.0", + "xtend": "~4.0.0" + } + }, + "node_modules/through2/node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "dev": true + }, + "node_modules/through2/node_modules/readable-stream": { + "version": "2.3.3", + "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.3.tgz", + "integrity": "sha512-m+qzzcn7KUxEmd1gMbchF+Y2eIUbieUaxkWtptyHywrX0rE8QEYqPC07Vuy4Wm32/xE16NcdBctb8S0Xe/5IeQ==", + "dev": true, + "dependencies": { + "core-util-is": "~1.0.0", + "inherits": "~2.0.3", + "isarray": "~1.0.0", + "process-nextick-args": "~1.0.6", + "safe-buffer": "~5.1.1", + "string_decoder": "~1.0.3", + "util-deprecate": "~1.0.1" + } + }, + "node_modules/through2/node_modules/string_decoder": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.0.3.tgz", + "integrity": "sha512-4AH6Z5fzNNBcH+6XDMfA/BTt87skxqJlO0lAh3Dker5zThcAxG6mKz+iGu308UKoPPQ8Dcqx/4JhujzltRa+hQ==", + "dev": true, + "dependencies": { + "safe-buffer": "~5.1.0" + } + }, + "node_modules/time-stamp": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/time-stamp/-/time-stamp-1.1.0.tgz", + "integrity": "sha1-dkpaEa9QVhkhsTPztE5hhofg9cM=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/timers-browserify": { + "version": "1.4.2", + "resolved": "https://registry.npmjs.org/timers-browserify/-/timers-browserify-1.4.2.tgz", + "integrity": "sha1-ycWLV1voQHN1y14kYtrO50NZ9B0=", + "dev": true, + "dependencies": { + "process": "~0.11.0" + }, + "engines": { + "node": ">=0.6.0" + } + }, + "node_modules/timers-ext": { + "version": "0.1.7", + "resolved": "https://registry.npmjs.org/timers-ext/-/timers-ext-0.1.7.tgz", + "integrity": "sha512-b85NUNzTSdodShTIbky6ZF02e8STtVVfD+fu4aXXShEELpozH+bCpJLYMPZbsABN2wDH7fJpqIoXxJpzbf0NqQ==", + "dev": true, + "dependencies": { + "es5-ext": "~0.10.46", + "next-tick": "1" + } + }, + "node_modules/timers-ext/node_modules/es5-ext": { + "version": "0.10.46", + "resolved": "https://registry.npmjs.org/es5-ext/-/es5-ext-0.10.46.tgz", + "integrity": "sha512-24XxRvJXNFwEMpJb3nOkiRJKRoupmjYmOPVlI65Qy2SrtxwOTB+g6ODjBKOtwEHbYrhWRty9xxOWLNdClT2djw==", + "dev": true, + "dependencies": { + "es6-iterator": "~2.0.3", + "es6-symbol": "~3.1.1", + "next-tick": "1" + } + }, + "node_modules/timers-ext/node_modules/es6-iterator": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/es6-iterator/-/es6-iterator-2.0.3.tgz", + "integrity": "sha1-p96IkUGgWpSwhUQDstCg+/qY87c=", + "dev": true, + "dependencies": { + "d": "1", + "es5-ext": "^0.10.35", + "es6-symbol": "^3.1.1" + } + }, + "node_modules/to-absolute-glob": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/to-absolute-glob/-/to-absolute-glob-2.0.2.tgz", + "integrity": "sha1-GGX0PZ50sIItufFFt4z/fQ98hJs=", + "dev": true, + "dependencies": { + "is-absolute": "^1.0.0", + "is-negated-glob": "^1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/to-arraybuffer": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/to-arraybuffer/-/to-arraybuffer-1.0.1.tgz", + "integrity": "sha1-fSKbH8xjfkZsoIEYCDanqr/4P0M=", + "dev": true + }, + "node_modules/to-object-path": { + "version": "0.3.0", + "resolved": "https://registry.npmjs.org/to-object-path/-/to-object-path-0.3.0.tgz", + "integrity": "sha1-KXWIt7Dn4KwI4E5nL4XB9JmeF68=", + "dev": true, + "dependencies": { + "kind-of": "^3.0.2" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/to-object-path/node_modules/kind-of": { + "version": "3.2.2", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-3.2.2.tgz", + "integrity": "sha1-MeohpzS6ubuw8yRm2JOupR5KPGQ=", + "dev": true, + "dependencies": { + "is-buffer": "^1.1.5" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/to-regex": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/to-regex/-/to-regex-3.0.2.tgz", + "integrity": "sha512-FWtleNAtZ/Ki2qtqej2CXTOayOH9bHDQF+Q48VpWyDXjbYxA4Yz8iDB31zXOBUlOHHKidDbqGVrTUvQMPmBGBw==", + "dev": true, + "dependencies": { + "define-property": "^2.0.2", + "extend-shallow": "^3.0.2", + "regex-not": "^1.0.2", + "safe-regex": "^1.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/to-regex-range": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/to-regex-range/-/to-regex-range-2.1.1.tgz", + "integrity": "sha1-fIDBe53+vlmeJzZ+DU3VWQFB2zg=", + "dev": true, + "dependencies": { + "is-number": "^3.0.0", + "repeat-string": "^1.6.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/to-through": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/to-through/-/to-through-2.0.0.tgz", + "integrity": "sha1-/JKtq6ByZHvAtn1rA2ZKoZUJOvY=", + "dev": true, + "dependencies": { + "through2": "^2.0.3" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/tsconfig": { + "version": "5.0.3", + "resolved": "https://registry.npmjs.org/tsconfig/-/tsconfig-5.0.3.tgz", + "integrity": "sha1-X0J45wGACWeo/Dg/0ZZIh48qbjo=", + "dev": true, + "dependencies": { + "any-promise": "^1.3.0", + "parse-json": "^2.2.0", + "strip-bom": "^2.0.0", + "strip-json-comments": "^2.0.0" + } + }, + "node_modules/tsify": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/tsify/-/tsify-3.0.4.tgz", + "integrity": "sha512-y75+qgB41YS8HJck+jmSIn395I4qRGtm5ZELzvNh80Llzh8ojPWp47jm0ZoIJesNYVzbqEyLzgYXV9d/calvVg==", + "dev": true, + "dependencies": { + "convert-source-map": "^1.1.0", + "fs.realpath": "^1.0.0", + "object-assign": "^4.1.0", + "semver": "^5.1.0", + "through2": "^2.0.0", + "tsconfig": "^5.0.3" + }, + "engines": { + "node": ">=0.12" + } + }, + "node_modules/tty-browserify": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/tty-browserify/-/tty-browserify-0.0.1.tgz", + "integrity": "sha512-C3TaO7K81YvjCgQH9Q1S3R3P3BtN3RIM8n+OvX4il1K1zgE8ZhI0op7kClgkxtutIE8hQrcrHBXvIheqKUUCxw==", + "dev": true + }, + "node_modules/typedarray": { + "version": "0.0.6", + "resolved": "https://registry.npmjs.org/typedarray/-/typedarray-0.0.6.tgz", + "integrity": "sha1-hnrHTjhkGHsdPUfZlqeOxciDB3c=", + "dev": true + }, + "node_modules/typescript": { + "version": "2.9.2", + "resolved": "https://registry.npmjs.org/typescript/-/typescript-2.9.2.tgz", + "integrity": "sha512-Gr4p6nFNaoufRIY4NMdpQRNmgxVIGMs4Fcu/ujdYk3nAZqk7supzBE9idmvfZIlH/Cuj//dvi+019qEue9lV0w==", + "dev": true, + "bin": { + "tsc": "bin/tsc", + "tsserver": "bin/tsserver" + }, + "engines": { + "node": ">=4.2.0" + } + }, + "node_modules/uglify-js": { + "version": "3.4.9", + "resolved": "https://registry.npmjs.org/uglify-js/-/uglify-js-3.4.9.tgz", + "integrity": "sha512-8CJsbKOtEbnJsTyv6LE6m6ZKniqMiFWmm9sRbopbkGs3gMPPfd3Fh8iIA4Ykv5MgaTbqHr4BaoGLJLZNhsrW1Q==", + "dev": true, + "dependencies": { + "commander": "~2.17.1", + "source-map": "~0.6.1" + }, + "bin": { + "uglifyjs": "bin/uglifyjs" + }, + "engines": { + "node": ">=0.8.0" + } + }, + "node_modules/uglify-js/node_modules/source-map": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/umd": { + "version": "3.0.3", + "resolved": "https://registry.npmjs.org/umd/-/umd-3.0.3.tgz", + "integrity": "sha512-4IcGSufhFshvLNcMCV80UnQVlZ5pMOC8mvNPForqwA4+lzYQuetTESLDQkeLmihq8bRcnpbQa48Wb8Lh16/xow==", + "dev": true, + "bin": { + "umd": "bin/cli.js" + } + }, + "node_modules/unc-path-regex": { + "version": "0.1.2", + "resolved": "https://registry.npmjs.org/unc-path-regex/-/unc-path-regex-0.1.2.tgz", + "integrity": "sha1-5z3T17DXxe2G+6xrCufYxqadUPo=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/undeclared-identifiers": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/undeclared-identifiers/-/undeclared-identifiers-1.1.2.tgz", + "integrity": "sha512-13EaeocO4edF/3JKime9rD7oB6QI8llAGhgn5fKOPyfkJbRb6NFv9pYV6dFEmpa4uRjKeBqLZP8GpuzqHlKDMQ==", + "dev": true, + "dependencies": { + "acorn-node": "^1.3.0", + "get-assigned-identifiers": "^1.2.0", + "simple-concat": "^1.0.0", + "xtend": "^4.0.1" + }, + "bin": { + "undeclared-identifiers": "bin.js" + } + }, + "node_modules/undertaker": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/undertaker/-/undertaker-1.2.0.tgz", + "integrity": "sha1-M52kZGJS0ILcN45wgGcpl1DhG0k=", + "dev": true, + "dependencies": { + "arr-flatten": "^1.0.1", + "arr-map": "^2.0.0", + "bach": "^1.0.0", + "collection-map": "^1.0.0", + "es6-weak-map": "^2.0.1", + "last-run": "^1.1.0", + "object.defaults": "^1.0.0", + "object.reduce": "^1.0.0", + "undertaker-registry": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/undertaker-registry": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/undertaker-registry/-/undertaker-registry-1.0.1.tgz", + "integrity": "sha1-XkvaMI5KiirlhPm5pDWaSZglzFA=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/union-value": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/union-value/-/union-value-1.0.0.tgz", + "integrity": "sha1-XHHDTLW61dzr4+oM0IIHulqhrqQ=", + "dev": true, + "dependencies": { + "arr-union": "^3.1.0", + "get-value": "^2.0.6", + "is-extendable": "^0.1.1", + "set-value": "^0.4.3" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/union-value/node_modules/extend-shallow": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extend-shallow/-/extend-shallow-2.0.1.tgz", + "integrity": "sha1-Ua99YUrZqfYQ6huvu5idaxxWiQ8=", + "dev": true, + "dependencies": { + "is-extendable": "^0.1.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/union-value/node_modules/set-value": { + "version": "0.4.3", + "resolved": "https://registry.npmjs.org/set-value/-/set-value-0.4.3.tgz", + "integrity": "sha1-fbCPnT0i3H945Trzw79GZuzfzPE=", + "dev": true, + "dependencies": { + "extend-shallow": "^2.0.1", + "is-extendable": "^0.1.1", + "is-plain-object": "^2.0.1", + "to-object-path": "^0.3.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/unique-stream": { + "version": "2.2.1", + "resolved": "https://registry.npmjs.org/unique-stream/-/unique-stream-2.2.1.tgz", + "integrity": "sha1-WqADz76Uxf+GbE59ZouxxNuts2k=", + "dev": true, + "dependencies": { + "json-stable-stringify": "^1.0.0", + "through2-filter": "^2.0.0" + } + }, + "node_modules/unique-stream/node_modules/json-stable-stringify": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/json-stable-stringify/-/json-stable-stringify-1.0.1.tgz", + "integrity": "sha1-mnWdOcXy/1A/1TAGRu1EX4jE+a8=", + "dev": true, + "dependencies": { + "jsonify": "~0.0.0" + } + }, + "node_modules/unset-value": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/unset-value/-/unset-value-1.0.0.tgz", + "integrity": "sha1-g3aHP30jNRef+x5vw6jtDfyKtVk=", + "dev": true, + "dependencies": { + "has-value": "^0.3.1", + "isobject": "^3.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/unset-value/node_modules/has-value": { + "version": "0.3.1", + "resolved": "https://registry.npmjs.org/has-value/-/has-value-0.3.1.tgz", + "integrity": "sha1-ex9YutpiyoJ+wKIHgCVlSEWZXh8=", + "dev": true, + "dependencies": { + "get-value": "^2.0.3", + "has-values": "^0.1.4", + "isobject": "^2.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/unset-value/node_modules/has-value/node_modules/isobject": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/isobject/-/isobject-2.1.0.tgz", + "integrity": "sha1-8GVWEJaj8dou9GJy+BXIQNh+DIk=", + "dev": true, + "dependencies": { + "isarray": "1.0.0" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/unset-value/node_modules/has-values": { + "version": "0.1.4", + "resolved": "https://registry.npmjs.org/has-values/-/has-values-0.1.4.tgz", + "integrity": "sha1-bWHeldkd/Km5oCCJrThL/49it3E=", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/unset-value/node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "dev": true + }, + "node_modules/upath": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/upath/-/upath-1.1.0.tgz", + "integrity": "sha512-bzpH/oBhoS/QI/YtbkqCg6VEiPYjSZtrHQM6/QnJS6OL9pKUFLqb3aFh4Scvwm45+7iAgiMkLhSbaZxUqmrprw==", + "dev": true, + "engines": { + "node": ">=4" + } + }, + "node_modules/urix": { + "version": "0.1.0", + "resolved": "https://registry.npmjs.org/urix/-/urix-0.1.0.tgz", + "integrity": "sha1-2pN/emLiH+wf0Y1Js1wpNQZ6bHI=", + "dev": true + }, + "node_modules/url": { + "version": "0.11.0", + "resolved": "https://registry.npmjs.org/url/-/url-0.11.0.tgz", + "integrity": "sha1-ODjpfPxgUh63PFJajlW/3Z4uKPE=", + "dev": true, + "dependencies": { + "punycode": "1.3.2", + "querystring": "0.2.0" + } + }, + "node_modules/url/node_modules/punycode": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.3.2.tgz", + "integrity": "sha1-llOgNvt8HuQjQvIyXM7v6jkmxI0=", + "dev": true + }, + "node_modules/use": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/use/-/use-3.1.1.tgz", + "integrity": "sha512-cwESVXlO3url9YWlFW/TA9cshCEhtu7IKJ/p5soJ/gGpj7vbvFrAY/eIioQ6Dw23KjZhYgiIo8HOs1nQ2vr/oQ==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/util": { + "version": "0.10.4", + "resolved": "https://registry.npmjs.org/util/-/util-0.10.4.tgz", + "integrity": "sha512-0Pm9hTQ3se5ll1XihRic3FDIku70C+iHUdT/W926rSgHV5QgXsYbKZN8MSC3tJtSkhuROzvsQjAaFENRXr+19A==", + "dev": true, + "dependencies": { + "inherits": "2.0.3" + } + }, + "node_modules/util-deprecate": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", + "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=", + "dev": true + }, + "node_modules/v8flags": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/v8flags/-/v8flags-3.1.1.tgz", + "integrity": "sha512-iw/1ViSEaff8NJ3HLyEjawk/8hjJib3E7pvG4pddVXfUg1983s3VGsiClDjhK64MQVDGqc1Q8r18S4VKQZS9EQ==", + "dev": true, + "dependencies": { + "homedir-polyfill": "^1.0.1" + }, + "engines": { + "node": ">= 0.10.0" + } + }, + "node_modules/validate-npm-package-license": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/validate-npm-package-license/-/validate-npm-package-license-3.0.4.tgz", + "integrity": "sha512-DpKm2Ui/xN7/HQKCtpZxoRWBhZ9Z0kqtygG8XCgNQ8ZlDnxuQmWhj566j8fN4Cu3/JmbhsDo7fcAJq4s9h27Ew==", + "dev": true, + "dependencies": { + "spdx-correct": "^3.0.0", + "spdx-expression-parse": "^3.0.0" + } + }, + "node_modules/value-or-function": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/value-or-function/-/value-or-function-3.0.0.tgz", + "integrity": "sha1-HCQ6ULWVwb5Up1S/7OhWO5/42BM=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/vinyl": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/vinyl/-/vinyl-2.2.0.tgz", + "integrity": "sha512-MBH+yP0kC/GQ5GwBqrTPTzEfiiLjta7hTtvQtbxBgTeSXsmKQRQecjibMbxIXzVT3Y9KJK+drOz1/k+vsu8Nkg==", + "dev": true, + "dependencies": { + "clone": "^2.1.1", + "clone-buffer": "^1.0.0", + "clone-stats": "^1.0.0", + "cloneable-readable": "^1.0.0", + "remove-trailing-separator": "^1.0.1", + "replace-ext": "^1.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/vinyl-buffer": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/vinyl-buffer/-/vinyl-buffer-1.0.1.tgz", + "integrity": "sha1-lsGjR5uMU5JULGEgKQE7Wyf4i78=", + "dev": true, + "dependencies": { + "bl": "^1.2.1", + "through2": "^2.0.3" + } + }, + "node_modules/vinyl-fs": { + "version": "3.0.3", + "resolved": "https://registry.npmjs.org/vinyl-fs/-/vinyl-fs-3.0.3.tgz", + "integrity": "sha512-vIu34EkyNyJxmP0jscNzWBSygh7VWhqun6RmqVfXePrOwi9lhvRs//dOaGOTRUQr4tx7/zd26Tk5WeSVZitgng==", + "dev": true, + "dependencies": { + "fs-mkdirp-stream": "^1.0.0", + "glob-stream": "^6.1.0", + "graceful-fs": "^4.0.0", + "is-valid-glob": "^1.0.0", + "lazystream": "^1.0.0", + "lead": "^1.0.0", + "object.assign": "^4.0.4", + "pumpify": "^1.3.5", + "readable-stream": "^2.3.3", + "remove-bom-buffer": "^3.0.0", + "remove-bom-stream": "^1.2.0", + "resolve-options": "^1.1.0", + "through2": "^2.0.0", + "to-through": "^2.0.0", + "value-or-function": "^3.0.0", + "vinyl": "^2.0.0", + "vinyl-sourcemap": "^1.1.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/vinyl-source-stream": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/vinyl-source-stream/-/vinyl-source-stream-2.0.0.tgz", + "integrity": "sha1-84pa+53R6Ttl1VBGmsYYKsT1S44=", + "dev": true, + "dependencies": { + "through2": "^2.0.3", + "vinyl": "^2.1.0" + } + }, + "node_modules/vinyl-sourcemap": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/vinyl-sourcemap/-/vinyl-sourcemap-1.1.0.tgz", + "integrity": "sha1-kqgAWTo4cDqM2xHYswCtS+Y7PhY=", + "dev": true, + "dependencies": { + "append-buffer": "^1.0.2", + "convert-source-map": "^1.5.0", + "graceful-fs": "^4.1.6", + "normalize-path": "^2.1.1", + "now-and-later": "^2.0.0", + "remove-bom-buffer": "^3.0.0", + "vinyl": "^2.0.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/vinyl-sourcemap/node_modules/convert-source-map": { + "version": "1.6.0", + "resolved": "https://registry.npmjs.org/convert-source-map/-/convert-source-map-1.6.0.tgz", + "integrity": "sha512-eFu7XigvxdZ1ETfbgPBohgyQ/Z++C0eEhTor0qRwBw9unw+L0/6V8wkSuGgzdThkiS5lSpdptOQPD8Ak40a+7A==", + "dev": true, + "dependencies": { + "safe-buffer": "~5.1.1" + } + }, + "node_modules/vinyl-sourcemaps-apply": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/vinyl-sourcemaps-apply/-/vinyl-sourcemaps-apply-0.2.1.tgz", + "integrity": "sha1-q2VJ1h0XLCsbh75cUI0jnI74dwU=", + "dev": true, + "dependencies": { + "source-map": "^0.5.1" + } + }, + "node_modules/vinyl/node_modules/clone": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/clone/-/clone-2.1.2.tgz", + "integrity": "sha1-G39Ln1kfHo+DZwQBYANFoCiHQ18=", + "dev": true, + "engines": { + "node": ">=0.8" + } + }, + "node_modules/vinyl/node_modules/clone-stats": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/clone-stats/-/clone-stats-1.0.0.tgz", + "integrity": "sha1-s3gt/4u1R04Yuba/D9/ngvh3doA=", + "dev": true + }, + "node_modules/vinyl/node_modules/replace-ext": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/replace-ext/-/replace-ext-1.0.0.tgz", + "integrity": "sha1-3mMSg3P8v3w8z6TeWkgMRaZ5WOs=", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/vm-browserify": { + "version": "0.0.4", + "resolved": "https://registry.npmjs.org/vm-browserify/-/vm-browserify-0.0.4.tgz", + "integrity": "sha1-XX6kW7755Kb/ZflUOOCofDV9WnM=", + "dev": true, + "dependencies": { + "indexof": "0.0.1" + } + }, + "node_modules/which": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/which/-/which-1.3.1.tgz", + "integrity": "sha512-HxJdYWq1MTIQbJ3nw0cqssHoTNU267KlrDuGZ1WYlxDStUtKUhOaJmh112/TZmHxxUfuJqPXSOm7tDyas0OSIQ==", + "dev": true, + "dependencies": { + "isexe": "^2.0.0" + }, + "bin": { + "which": "bin/which" + } + }, + "node_modules/which-module": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/which-module/-/which-module-1.0.0.tgz", + "integrity": "sha1-u6Y8qGGUiZT/MHc2CJ47lgJsKk8=", + "dev": true + }, + "node_modules/wrap-ansi": { + "version": "2.1.0", + "resolved": "http://registry.npmjs.org/wrap-ansi/-/wrap-ansi-2.1.0.tgz", + "integrity": "sha1-2Pw9KE3QV5T+hJc8rs3Rz4JP3YU=", + "dev": true, + "dependencies": { + "string-width": "^1.0.1", + "strip-ansi": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/wrappy": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", + "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=", + "dev": true + }, + "node_modules/xtend": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/xtend/-/xtend-4.0.1.tgz", + "integrity": "sha1-pcbVMr5lbiPbgg77lDofBJmNY68=", + "dev": true, + "engines": { + "node": ">=0.4" + } + }, + "node_modules/y18n": { + "version": "3.2.1", + "resolved": "https://registry.npmjs.org/y18n/-/y18n-3.2.1.tgz", + "integrity": "sha1-bRX7qITAhnnA136I53WegR4H+kE=", + "dev": true + }, + "node_modules/yargs": { + "version": "7.1.0", + "resolved": "https://registry.npmjs.org/yargs/-/yargs-7.1.0.tgz", + "integrity": "sha1-a6MY6xaWFyf10oT46gA+jWFU0Mg=", + "dev": true, + "dependencies": { + "camelcase": "^3.0.0", + "cliui": "^3.2.0", + "decamelize": "^1.1.1", + "get-caller-file": "^1.0.1", + "os-locale": "^1.4.0", + "read-pkg-up": "^1.0.1", + "require-directory": "^2.1.1", + "require-main-filename": "^1.0.1", + "set-blocking": "^2.0.0", + "string-width": "^1.0.2", + "which-module": "^1.0.0", + "y18n": "^3.2.1", + "yargs-parser": "^5.0.0" + } + }, + "node_modules/yargs-parser": { + "version": "5.0.0", + "resolved": "https://registry.npmjs.org/yargs-parser/-/yargs-parser-5.0.0.tgz", + "integrity": "sha1-J17PDX/+Bcd+ZOfIbkzZS/DhIoo=", + "dev": true, + "dependencies": { + "camelcase": "^3.0.0" + } + } + }, "dependencies": { "@gulp-sourcemaps/identity-map": { "version": "1.0.2", @@ -41,16 +6243,6 @@ "through2": "^2.0.3" } }, - "JSONStream": { - "version": "1.3.5", - "resolved": "https://registry.npmjs.org/JSONStream/-/JSONStream-1.3.5.tgz", - "integrity": "sha512-E+iruNOY8VV9s4JEbe1aNEm6MiszPRr/UfcHMz0TQh1BXSxHK+ASV1R6W4HpjBhSeS+54PIsAMCBmwD06LLsqQ==", - "dev": true, - "requires": { - "jsonparse": "^1.2.0", - "through": ">=2.2.7 <3" - } - }, "acorn": { "version": "6.4.1", "resolved": "https://registry.npmjs.org/acorn/-/acorn-6.4.1.tgz", @@ -511,9 +6703,9 @@ "integrity": "sha512-erYug8XoqzU3IfcU8fUgyHqyOXqIE4tUTTQ+7mqUjQlvnXkOO6OlT9c/ZoJVHYoAaqGxr09CN53G7XIsO4KtWA==", "dev": true, "requires": { - "JSONStream": "^1.0.3", "combine-source-map": "~0.8.0", "defined": "^1.0.0", + "JSONStream": "^1.0.3", "safe-buffer": "^5.1.1", "through2": "^2.0.0", "umd": "^3.0.0" @@ -542,7 +6734,6 @@ "integrity": "sha512-gKfOsNQv/toWz+60nSPfYzuwSEdzvV2WdxrVPUbPD/qui44rAkB3t3muNtmmGYHqrG56FGwX9SUEQmzNLAeS7g==", "dev": true, "requires": { - "JSONStream": "^1.0.3", "assert": "^1.4.0", "browser-pack": "^6.0.1", "browser-resolve": "^1.11.0", @@ -564,6 +6755,7 @@ "https-browserify": "^1.0.0", "inherits": "~2.0.1", "insert-module-globals": "^7.0.0", + "JSONStream": "^1.0.3", "labeled-stream-splicer": "^2.0.0", "module-deps": "^4.0.8", "os-browserify": "~0.3.0", @@ -1723,18 +7915,24 @@ "dependencies": { "abbrev": { "version": "1.1.1", + "resolved": "https://registry.npmjs.org/abbrev/-/abbrev-1.1.1.tgz", + "integrity": "sha512-nne9/IiQ/hzIhY6pdDnbBtz7DjPTKrY00P/zvPSm5pOFkl6xuGrGnXn/VtTNNfNtAfZ9/1RtehkszU9qcTii0Q==", "bundled": true, "dev": true, "optional": true }, "ansi-regex": { "version": "2.1.1", + "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-2.1.1.tgz", + "integrity": "sha1-w7M6te42DYbg5ijwRorn7yfWVN8=", "bundled": true, "dev": true, "optional": true }, "aproba": { "version": "1.2.0", + "resolved": "https://registry.npmjs.org/aproba/-/aproba-1.2.0.tgz", + "integrity": "sha512-Y9J6ZjXtoYh8RnXVCMOU/ttDmk1aBjunq9vO0ta5x85WDQiQfUF9sIPBITdbiiIVcBo03Hi3jMxigBtsddlXRw==", "bundled": true, "dev": true, "optional": true @@ -1751,12 +7949,16 @@ }, "balanced-match": { "version": "1.0.0", + "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.0.tgz", + "integrity": "sha1-ibTRmasr7kneFk6gK4nORi1xt2c=", "bundled": true, "dev": true, "optional": true }, "brace-expansion": { "version": "1.1.11", + "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", + "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", "bundled": true, "dev": true, "optional": true, @@ -1773,24 +7975,32 @@ }, "code-point-at": { "version": "1.1.0", + "resolved": "https://registry.npmjs.org/code-point-at/-/code-point-at-1.1.0.tgz", + "integrity": "sha1-DQcLTQQ6W+ozovGkDi7bPZpMz3c=", "bundled": true, "dev": true, "optional": true }, "concat-map": { "version": "0.0.1", + "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", + "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=", "bundled": true, "dev": true, "optional": true }, "console-control-strings": { "version": "1.1.0", + "resolved": "https://registry.npmjs.org/console-control-strings/-/console-control-strings-1.1.0.tgz", + "integrity": "sha1-PXz0Rk22RG6mRL9LOVB/mFEAjo4=", "bundled": true, "dev": true, "optional": true }, "core-util-is": { "version": "1.0.2", + "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.2.tgz", + "integrity": "sha1-tf1UIgqivFq1eqtxQMlAdUUDwac=", "bundled": true, "dev": true, "optional": true @@ -1812,12 +8022,16 @@ }, "delegates": { "version": "1.0.0", + "resolved": "https://registry.npmjs.org/delegates/-/delegates-1.0.0.tgz", + "integrity": "sha1-hMbhWbgZBP3KWaDvRM2HDTElD5o=", "bundled": true, "dev": true, "optional": true }, "detect-libc": { "version": "1.0.3", + "resolved": "https://registry.npmjs.org/detect-libc/-/detect-libc-1.0.3.tgz", + "integrity": "sha1-+hN8S9aY7fVc1c0CrFWfkaTEups=", "bundled": true, "dev": true, "optional": true @@ -1833,12 +8047,16 @@ }, "fs.realpath": { "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", + "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=", "bundled": true, "dev": true, "optional": true }, "gauge": { "version": "2.7.4", + "resolved": "https://registry.npmjs.org/gauge/-/gauge-2.7.4.tgz", + "integrity": "sha1-LANAXHU4w51+s3sxcCLjJfsBi/c=", "bundled": true, "dev": true, "optional": true, @@ -1869,6 +8087,8 @@ }, "has-unicode": { "version": "2.0.1", + "resolved": "https://registry.npmjs.org/has-unicode/-/has-unicode-2.0.1.tgz", + "integrity": "sha1-4Ob+aijPUROIVeCG0Wkedx3iqLk=", "bundled": true, "dev": true, "optional": true @@ -1893,6 +8113,8 @@ }, "inflight": { "version": "1.0.6", + "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", + "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", "bundled": true, "dev": true, "optional": true, @@ -1909,6 +8131,8 @@ }, "is-fullwidth-code-point": { "version": "1.0.0", + "resolved": "https://registry.npmjs.org/is-fullwidth-code-point/-/is-fullwidth-code-point-1.0.0.tgz", + "integrity": "sha1-754xOG8DGn8NZDr4L95QxFfvAMs=", "bundled": true, "dev": true, "optional": true, @@ -1918,12 +8142,16 @@ }, "isarray": { "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", "bundled": true, "dev": true, "optional": true }, "minimatch": { "version": "3.0.4", + "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", + "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", "bundled": true, "dev": true, "optional": true, @@ -2038,6 +8266,8 @@ }, "npmlog": { "version": "4.1.2", + "resolved": "https://registry.npmjs.org/npmlog/-/npmlog-4.1.2.tgz", + "integrity": "sha512-2uUqazuKlTaSI/dC8AzicUck7+IrEaOnN/e0jd3Xtt1KcGpwx30v50mL7oPyr/h9bL3E4aZccVwpwP+5W9Vjkg==", "bundled": true, "dev": true, "optional": true, @@ -2050,18 +8280,24 @@ }, "number-is-nan": { "version": "1.0.1", + "resolved": "https://registry.npmjs.org/number-is-nan/-/number-is-nan-1.0.1.tgz", + "integrity": "sha1-CXtgK1NCKlIsGvuHkDGDNpQaAR0=", "bundled": true, "dev": true, "optional": true }, "object-assign": { "version": "4.1.1", + "resolved": "https://registry.npmjs.org/object-assign/-/object-assign-4.1.1.tgz", + "integrity": "sha1-IQmtx5ZYh8/AXLvUQsrIv7s2CGM=", "bundled": true, "dev": true, "optional": true }, "once": { "version": "1.4.0", + "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", + "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", "bundled": true, "dev": true, "optional": true, @@ -2071,18 +8307,24 @@ }, "os-homedir": { "version": "1.0.2", + "resolved": "https://registry.npmjs.org/os-homedir/-/os-homedir-1.0.2.tgz", + "integrity": "sha1-/7xJiDNuDoM94MFox+8VISGqf7M=", "bundled": true, "dev": true, "optional": true }, "os-tmpdir": { "version": "1.0.2", + "resolved": "https://registry.npmjs.org/os-tmpdir/-/os-tmpdir-1.0.2.tgz", + "integrity": "sha1-u+Z0BseaqFxc/sdm/lc0VV36EnQ=", "bundled": true, "dev": true, "optional": true }, "osenv": { "version": "0.1.5", + "resolved": "https://registry.npmjs.org/osenv/-/osenv-0.1.5.tgz", + "integrity": "sha512-0CWcCECdMVc2Rw3U5w9ZjqX6ga6ubk1xDVKxtBQPK7wis/0F2r9T6k4ydGYhecl7YUBxBVxhL5oisPsNxAPe2g==", "bundled": true, "dev": true, "optional": true, @@ -2093,6 +8335,8 @@ }, "path-is-absolute": { "version": "1.0.1", + "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", + "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=", "bundled": true, "dev": true, "optional": true @@ -2147,12 +8391,16 @@ }, "safer-buffer": { "version": "2.1.2", + "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", + "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==", "bundled": true, "dev": true, "optional": true }, "sax": { "version": "1.2.4", + "resolved": "https://registry.npmjs.org/sax/-/sax-1.2.4.tgz", + "integrity": "sha512-NqVDv9TpANUjFm0N8uM5GxL36UgKi9/atZw+x7YFnQ8ckwFGKrl4xX4yWtrey3UJm5nP1kUbnYgLopqWNSRhWw==", "bundled": true, "dev": true, "optional": true @@ -2165,38 +8413,48 @@ }, "set-blocking": { "version": "2.0.0", + "resolved": "https://registry.npmjs.org/set-blocking/-/set-blocking-2.0.0.tgz", + "integrity": "sha1-BF+XgtARrppoA93TgrJDkrPYkPc=", "bundled": true, "dev": true, "optional": true }, "signal-exit": { "version": "3.0.2", + "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.2.tgz", + "integrity": "sha1-tf3AjxKH6hF4Yo5BXiUTK3NkbG0=", "bundled": true, "dev": true, "optional": true }, - "string-width": { - "version": "1.0.2", + "string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", "bundled": true, "dev": true, "optional": true, "requires": { - "code-point-at": "^1.0.0", - "is-fullwidth-code-point": "^1.0.0", - "strip-ansi": "^3.0.0" + "safe-buffer": "~5.1.0" } }, - "string_decoder": { - "version": "1.1.1", + "string-width": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/string-width/-/string-width-1.0.2.tgz", + "integrity": "sha1-EYvfW4zcUaKn5w0hHgfisLmxB9M=", "bundled": true, "dev": true, "optional": true, "requires": { - "safe-buffer": "~5.1.0" + "code-point-at": "^1.0.0", + "is-fullwidth-code-point": "^1.0.0", + "strip-ansi": "^3.0.0" } }, "strip-ansi": { "version": "3.0.1", + "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-3.0.1.tgz", + "integrity": "sha1-ajhfuIU9lS1f8F0Oiq+UJ43GPc8=", "bundled": true, "dev": true, "optional": true, @@ -2206,6 +8464,8 @@ }, "strip-json-comments": { "version": "2.0.1", + "resolved": "https://registry.npmjs.org/strip-json-comments/-/strip-json-comments-2.0.1.tgz", + "integrity": "sha1-PFMZQukIwml8DsNEhYwobHygpgo=", "bundled": true, "dev": true, "optional": true @@ -2227,6 +8487,8 @@ }, "util-deprecate": { "version": "1.0.2", + "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", + "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=", "bundled": true, "dev": true, "optional": true @@ -2242,6 +8504,8 @@ }, "wrappy": { "version": "1.0.2", + "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", + "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=", "bundled": true, "dev": true, "optional": true @@ -2670,11 +8934,11 @@ "integrity": "sha512-VE6NlW+WGn2/AeOMd496AHFYmE7eLKkUY6Ty31k4og5vmA3Fjuwe9v6ifH6Xx/Hz27QvdoMoviw1/pqWRB09Sw==", "dev": true, "requires": { - "JSONStream": "^1.0.3", "acorn-node": "^1.5.2", "combine-source-map": "^0.8.0", "concat-stream": "^1.6.1", "is-buffer": "^1.1.0", + "JSONStream": "^1.0.3", "path-is-absolute": "^1.0.1", "process": "~0.11.0", "through2": "^2.0.0", @@ -2953,6 +9217,16 @@ "integrity": "sha1-P02uSpH6wxX3EGL4UhzCOfE2YoA=", "dev": true }, + "JSONStream": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/JSONStream/-/JSONStream-1.3.5.tgz", + "integrity": "sha512-E+iruNOY8VV9s4JEbe1aNEm6MiszPRr/UfcHMz0TQh1BXSxHK+ASV1R6W4HpjBhSeS+54PIsAMCBmwD06LLsqQ==", + "dev": true, + "requires": { + "jsonparse": "^1.2.0", + "through": ">=2.2.7 <3" + } + }, "just-debounce": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/just-debounce/-/just-debounce-1.0.0.tgz", @@ -3266,7 +9540,6 @@ "integrity": "sha1-IyFYM/HaE/1gbMuAh7RIUty4If0=", "dev": true, "requires": { - "JSONStream": "^1.0.3", "browser-resolve": "^1.7.0", "cached-path-relative": "^1.0.0", "concat-stream": "~1.5.0", @@ -3274,6 +9547,7 @@ "detective": "^4.0.0", "duplexer2": "^0.1.2", "inherits": "^2.0.1", + "JSONStream": "^1.0.3", "parents": "^1.0.0", "readable-stream": "^2.0.2", "resolve": "^1.1.3", @@ -4356,6 +10630,15 @@ "readable-stream": "^2.0.2" } }, + "string_decoder": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.0.3.tgz", + "integrity": "sha512-4AH6Z5fzNNBcH+6XDMfA/BTt87skxqJlO0lAh3Dker5zThcAxG6mKz+iGu308UKoPPQ8Dcqx/4JhujzltRa+hQ==", + "dev": true, + "requires": { + "safe-buffer": "~5.1.0" + } + }, "string-width": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/string-width/-/string-width-1.0.2.tgz", @@ -4367,15 +10650,6 @@ "strip-ansi": "^3.0.0" } }, - "string_decoder": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.0.3.tgz", - "integrity": "sha512-4AH6Z5fzNNBcH+6XDMfA/BTt87skxqJlO0lAh3Dker5zThcAxG6mKz+iGu308UKoPPQ8Dcqx/4JhujzltRa+hQ==", - "dev": true, - "requires": { - "safe-buffer": "~5.1.0" - } - }, "strip-ansi": { "version": "3.0.1", "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-3.0.1.tgz", diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 9158d83c..942798eb 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -1,6 +1,10 @@ -{-# OPTIONS_GHC -Wwarn #-} -{-# LANGUAGE CPP, ScopedTypeVariables, OverloadedStrings, Rank2Types #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TupleSections #-} +{-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock @@ -46,7 +50,7 @@ import Control.Monad.IO.Class (MonadIO(..)) import Data.Bifunctor (second) import Data.Foldable (forM_, foldl') import Data.Traversable (for) -import Data.List (isPrefixOf) +import Data.List (find, isPrefixOf, nub) import Control.Exception import Data.Maybe import Data.IORef @@ -75,6 +79,7 @@ import GHC.Utils.Error import GHC.Utils.Logger import GHC.Types.Name.Cache import GHC.Unit +import GHC.Unit.State (lookupUnit) import GHC.Utils.Panic (handleGhcException) import GHC.Data.FastString @@ -193,7 +198,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do forM_ (optShowInterfaceFile flags) $ \path -> liftIO $ do name_cache <- freshNameCache mIfaceFile <- readInterfaceFiles name_cache [(("", Nothing), path)] noChecks - forM_ mIfaceFile $ \(_, ifaceFile) -> do + forM_ mIfaceFile $ \(_,_, ifaceFile) -> do putMsg logger $ renderJson (jsonInterfaceFile ifaceFile) if not (null files) then do @@ -254,7 +259,7 @@ withGhc flags action = do readPackagesAndProcessModules :: [Flag] -> [String] - -> Ghc ([(DocPaths, InterfaceFile)], [Interface], LinkEnv) + -> Ghc ([(DocPaths, FilePath, InterfaceFile)], [Interface], LinkEnv) readPackagesAndProcessModules flags files = do -- Get packages supplied with --read-interface. let noChecks = Flag_BypassInterfaceVersonCheck `elem` flags @@ -262,28 +267,42 @@ readPackagesAndProcessModules flags files = do packages <- liftIO $ readInterfaceFiles name_cache (readIfaceArgs flags) noChecks -- Create the interfaces -- this is the core part of Haddock. - let ifaceFiles = map snd packages + let ifaceFiles = map (\(_, _, ifaceFile) -> ifaceFile) packages (ifaces, homeLinks) <- processModules (verbosity flags) files flags ifaceFiles return (packages, ifaces, homeLinks) renderStep :: Logger -> DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption - -> [(DocPaths, InterfaceFile)] -> [Interface] -> IO () + -> [(DocPaths, FilePath, InterfaceFile)] -> [Interface] -> IO () renderStep logger dflags unit_state flags sinceQual nameQual pkgs interfaces = do - updateHTMLXRefs pkgs + updateHTMLXRefs (map (\(docPath, _ifaceFilePath, ifaceFile) -> + ( case baseUrl flags of + Nothing -> fst docPath + Just url -> url packageName (ifUnitId ifaceFile) + , ifaceFile)) pkgs) let - ifaceFiles = map snd pkgs - installedIfaces = concatMap ifInstalledIfaces ifaceFiles + installedIfaces = + concatMap + (\(_, ifaceFilePath, ifaceFile) + -> (ifaceFilePath,) <$> ifInstalledIfaces ifaceFile) + pkgs extSrcMap = Map.fromList $ do - ((_, Just path), ifile) <- pkgs + ((_, Just path), _, ifile) <- pkgs iface <- ifInstalledIfaces ifile return (instMod iface, path) render logger dflags unit_state flags sinceQual nameQual interfaces installedIfaces extSrcMap + where + -- get package name from unit-id + packageName :: Unit -> String + packageName unit = + case lookupUnit unit_state unit of + Nothing -> show unit + Just pkg -> unitPackageNameString pkg -- | Render the interfaces with whatever backend is specified in the flags. render :: Logger -> DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption -> [Interface] - -> [InstalledInterface] -> Map Module FilePath -> IO () + -> [(FilePath, InstalledInterface)] -> Map Module FilePath -> IO () render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do let @@ -291,6 +310,7 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc unicode = Flag_UseUnicode `elem` flags pretty = Flag_PrettyHtml `elem` flags opt_wiki_urls = wikiUrls flags + opt_base_url = baseUrl flags opt_contents_url = optContentsUrl flags opt_index_url = optIndexUrl flags odir = outputDir flags @@ -305,7 +325,7 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc visibleIfaces = [ i | i <- ifaces, OptHide `notElem` ifaceOptions i ] -- /All/ visible interfaces including external package modules. - allIfaces = map toInstalledIface ifaces ++ installedIfaces + allIfaces = map toInstalledIface ifaces ++ map snd installedIfaces allVisibleIfaces = [ i | i <- allIfaces, OptHide `notElem` instOptions i ] pkgMod = fmap ifaceMod (listToMaybe ifaces) @@ -350,7 +370,7 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc sourceUrls' = (srcBase, srcModule', pkgSrcMap', pkgSrcLMap') installedMap :: Map Module InstalledInterface - installedMap = Map.fromList [ (unwire (instMod iface), iface) | iface <- installedIfaces ] + installedMap = Map.fromList [ (unwire (instMod iface), iface) | (_, iface) <- installedIfaces ] -- The user gives use base-4.9.0.0, but the InstalledInterface -- records the *wired in* identity base. So untranslate it @@ -373,6 +393,13 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc themes <- getThemes libDir flags >>= either bye return let withQuickjump = Flag_QuickJumpIndex `elem` flags + withBaseURL = isJust + . find (\flag -> case flag of + Flag_BaseURL base_url -> + base_url /= "." && base_url /= "./" + _ -> False + ) + $ flags when (Flag_GenIndex `elem` flags) $ do withTiming logger "ppHtmlIndex" (const ()) $ do @@ -382,7 +409,8 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc allVisibleIfaces pretty return () - copyHtmlBits odir libDir themes withQuickjump + unless withBaseURL $ + copyHtmlBits odir libDir themes withQuickjump when (Flag_GenContents `elem` flags) $ do withTiming logger "ppHtmlContents" (const ()) $ do @@ -394,17 +422,24 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc return () copyHtmlBits odir libDir themes withQuickjump + when withQuickjump $ void $ + ppJsonIndex odir sourceUrls' opt_wiki_urls + unicode Nothing qual + ifaces + (nub $ map fst installedIfaces) + when (Flag_Html `elem` flags) $ do withTiming logger "ppHtml" (const ()) $ do _ <- {-# SCC ppHtml #-} ppHtml unit_state title pkgStr visibleIfaces reexportedIfaces odir prologue - themes opt_mathjax sourceUrls' opt_wiki_urls + themes opt_mathjax sourceUrls' opt_wiki_urls opt_base_url opt_contents_url opt_index_url unicode sincePkg qual pretty withQuickjump return () - copyHtmlBits odir libDir themes withQuickjump - writeHaddockMeta odir withQuickjump + unless withBaseURL $ do + copyHtmlBits odir libDir themes withQuickjump + writeHaddockMeta odir withQuickjump -- TODO: we throw away Meta for both Hoogle and LaTeX right now, -- might want to fix that if/when these two get some work on them @@ -451,7 +486,7 @@ render log' dflags unit_state flags sinceQual qual ifaces installedIfaces extSrc readInterfaceFiles :: NameCache -> [(DocPaths, FilePath)] -> Bool - -> IO [(DocPaths, InterfaceFile)] + -> IO [(DocPaths, FilePath, InterfaceFile)] readInterfaceFiles name_cache pairs bypass_version_check = do catMaybes `liftM` mapM ({-# SCC readInterfaceFile #-} tryReadIface) pairs where @@ -463,7 +498,7 @@ readInterfaceFiles name_cache pairs bypass_version_check = do putStrLn (" " ++ err) putStrLn "Skipping this interface." return Nothing - Right f -> return $ Just (paths, f) + Right f -> return (Just (paths, file, f)) ------------------------------------------------------------------------------- @@ -684,12 +719,12 @@ hypSrcWarnings flags = do isSourceCssFlag _ = False -updateHTMLXRefs :: [(DocPaths, InterfaceFile)] -> IO () +updateHTMLXRefs :: [(FilePath, InterfaceFile)] -> IO () updateHTMLXRefs packages = do writeIORef html_xrefs_ref (Map.fromList mapping) writeIORef html_xrefs_ref' (Map.fromList mapping') where - mapping = [ (instMod iface, html) | ((html, _), ifaces) <- packages + mapping = [ (instMod iface, html) | (html, ifaces) <- packages , iface <- ifInstalledIfaces ifaces ] mapping' = [ (moduleName m, html) | (m, html) <- mapping ] diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs index d390a95a..b7674b24 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml.hs @@ -11,10 +11,11 @@ -- Stability : experimental -- Portability : portable ----------------------------------------------------------------------------- -{-# LANGUAGE CPP, NamedFieldPuns #-} +{-# LANGUAGE CPP, NamedFieldPuns, TupleSections, TypeApplications #-} module Haddock.Backends.Xhtml ( ppHtml, copyHtmlBits, ppHtmlIndex, ppHtmlContents, + ppJsonIndex ) where @@ -38,12 +39,16 @@ import Haddock.GhcUtils import Control.Monad ( when, unless ) import qualified Data.ByteString.Builder as Builder +import Data.Bifunctor ( bimap ) import Data.Char ( toUpper, isSpace ) +import Data.Either ( partitionEithers ) +import Data.Foldable ( traverse_) import Data.List ( sortBy, isPrefixOf, intersperse ) import Data.Maybe import System.Directory import System.FilePath hiding ( () ) import qualified System.IO as IO +import qualified System.FilePath as FilePath import Data.Map ( Map ) import qualified Data.Map as Map hiding ( Map ) import qualified Data.Set as Set hiding ( Set ) @@ -68,6 +73,7 @@ ppHtml :: UnitState -> Maybe String -- ^ The mathjax URL (--mathjax) -> SourceURLs -- ^ The source URL (--source) -> WikiURLs -- ^ The wiki URL (--wiki) + -> BaseURL -- ^ The base URL (--base-url) -> Maybe String -- ^ The contents URL (--use-contents) -> Maybe String -- ^ The index URL (--use-index) -> Bool -- ^ Whether to use unicode in output (--use-unicode) @@ -79,7 +85,7 @@ ppHtml :: UnitState ppHtml state doctitle maybe_package ifaces reexported_ifaces odir prologue themes maybe_mathjax_url maybe_source_url maybe_wiki_url - maybe_contents_url maybe_index_url unicode + maybe_base_url maybe_contents_url maybe_index_url unicode pkg qual debug withQuickjump = do let visible_ifaces = filter visible ifaces @@ -97,12 +103,12 @@ ppHtml state doctitle maybe_package ifaces reexported_ifaces odir prologue themes maybe_mathjax_url maybe_contents_url maybe_source_url maybe_wiki_url (map toInstalledIface visible_ifaces ++ reexported_ifaces) debug - when withQuickjump $ - ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual - visible_ifaces + when withQuickjump $ + ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual + visible_ifaces [] mapM_ (ppHtmlModule odir doctitle themes - maybe_mathjax_url maybe_source_url maybe_wiki_url + maybe_mathjax_url maybe_source_url maybe_wiki_url maybe_base_url maybe_contents_url maybe_index_url unicode pkg qual debug) visible_ifaces @@ -119,16 +125,23 @@ copyHtmlBits odir libdir themes withQuickjump = do return () -headHtml :: String -> Themes -> Maybe String -> Html -headHtml docTitle themes mathjax_url = - header << +headHtml :: String -> Themes -> Maybe String -> Maybe String -> Html +headHtml docTitle themes mathjax_url base_url = + header ! (maybe [] (\url -> [identifier "head", strAttr "data-base-url" url ]) base_url) + << [ meta ! [ httpequiv "Content-Type", content "text/html; charset=UTF-8"] , meta ! [ XHtml.name "viewport", content "width=device-width, initial-scale=1"] , thetitle << docTitle - , styleSheet themes - , thelink ! [ rel "stylesheet", thetype "text/css", href quickJumpCssFile] << noHtml + , styleSheet base_url themes + , thelink ! [ rel "stylesheet" + , thetype "text/css" + , href (withBaseURL base_url quickJumpCssFile) ] + << noHtml , thelink ! [ rel "stylesheet", thetype "text/css", href fontUrl] << noHtml - , script ! [src haddockJsFile, emptyAttr "async", thetype "text/javascript"] << noHtml + , script ! [ src (withBaseURL base_url haddockJsFile) + , emptyAttr "async" + , thetype "text/javascript" ] + << noHtml , script ! [thetype "text/x-mathjax-config"] << primHtml mjConf , script ! [src mjUrl, thetype "text/javascript"] << noHtml ] @@ -281,7 +294,7 @@ ppHtmlContents state odir doctitle _maybe_package | iface <- ifaces , instIsSig iface] html = - headHtml doctitle themes mathjax_url +++ + headHtml doctitle themes mathjax_url Nothing +++ bodyHtml doctitle Nothing maybe_source_url maybe_wiki_url Nothing maybe_index_url << [ @@ -361,6 +374,35 @@ mkNode pkg qual ss p (Node s leaf _pkg srcPkg short ts) = -- * Generate the index -------------------------------------------------------------------------------- +data JsonIndexEntry = JsonIndexEntry { + jieHtmlFragment :: String, + jieName :: String, + jieModule :: String, + jieLink :: String + } + deriving Show + +instance ToJSON JsonIndexEntry where + toJSON JsonIndexEntry + { jieHtmlFragment + , jieName + , jieModule + , jieLink } = + Object + [ "display_html" .= String jieHtmlFragment + , "name" .= String jieName + , "module" .= String jieModule + , "link" .= String jieLink + ] + +instance FromJSON JsonIndexEntry where + parseJSON = withObject "JsonIndexEntry" $ \v -> + JsonIndexEntry + <$> v .: "display_html" + <*> v .: "name" + <*> v .: "module" + <*> v .: "link" + ppJsonIndex :: FilePath -> SourceURLs -- ^ The source URL (--source) -> WikiURLs -- ^ The wiki URL (--wiki) @@ -368,34 +410,50 @@ ppJsonIndex :: FilePath -> Maybe Package -> QualOption -> [Interface] + -> [FilePath] -- ^ file paths to interface files + -- (--read-interface) -> IO () -ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual_opt ifaces = do +ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual_opt ifaces installedIfacesPaths = do createDirectoryIfMissing True odir - IO.withBinaryFile (joinPath [odir, indexJsonFile]) IO.WriteMode $ \h -> do - Builder.hPutBuilder h (encodeToBuilder modules) + (errors, installedIndexes) <- + partitionEithers + <$> traverse + (\ifaceFile -> + let indexFile = takeDirectory ifaceFile + FilePath. "doc-index.json" in + bimap (indexFile,) (map (fixLink ifaceFile)) + <$> eitherDecodeFile @[JsonIndexEntry] indexFile) + installedIfacesPaths + traverse_ (\(indexFile, err) -> putStrLn $ "haddock: Coudn't parse " ++ indexFile ++ ": " ++ err) + errors + IO.withBinaryFile (joinPath [odir, indexJsonFile]) IO.WriteMode $ \h -> + Builder.hPutBuilder + h (encodeToBuilder (encodeIndexes (concat installedIndexes))) where - modules :: Value - modules = Array (concatMap goInterface ifaces) - - goInterface :: Interface -> [Value] - goInterface iface = - concatMap (goExport mdl qual) (ifaceRnExportItems iface) + encodeIndexes :: [JsonIndexEntry] -> Value + encodeIndexes installedIndexes = + toJSON + (concatMap fromInterface ifaces + ++ installedIndexes) + + fromInterface :: Interface -> [JsonIndexEntry] + fromInterface iface = + mkIndex mdl qual `mapMaybe` ifaceRnExportItems iface where aliases = ifaceModuleAliases iface qual = makeModuleQual qual_opt aliases mdl mdl = ifaceMod iface - goExport :: Module -> Qualification -> ExportItem DocNameI -> [Value] - goExport mdl qual item + mkIndex :: Module -> Qualification -> ExportItem DocNameI -> Maybe JsonIndexEntry + mkIndex mdl qual item | Just item_html <- processExport True links_info unicode pkg qual item - = [ Object - [ "display_html" .= String (showHtmlFragment item_html) - , "name" .= String (unwords (map getOccString names)) - , "module" .= String (moduleString mdl) - , "link" .= String (fromMaybe "" (listToMaybe (map (nameLink mdl) names))) - ] - ] - | otherwise = [] + = Just JsonIndexEntry + { jieHtmlFragment = showHtmlFragment item_html + , jieName = unwords (map getOccString names) + , jieModule = moduleString mdl + , jieLink = fromMaybe "" (listToMaybe (map (nameLink mdl) names)) + } + | otherwise = Nothing where names = exportName item ++ exportSubs item @@ -413,6 +471,13 @@ ppJsonIndex odir maybe_source_url maybe_wiki_url unicode pkg qual_opt ifaces = d links_info = (maybe_source_url, maybe_wiki_url) + -- update link using relative path to output directory + fixLink :: FilePath + -> JsonIndexEntry -> JsonIndexEntry + fixLink ifaceFile jie = + jie { jieLink = makeRelative odir (takeDirectory ifaceFile) + FilePath. jieLink jie } + ppHtmlIndex :: FilePath -> String -> Maybe String @@ -441,7 +506,7 @@ ppHtmlIndex odir doctitle _maybe_package themes where indexPage showLetters ch items = - headHtml (doctitle ++ " (" ++ indexName ch ++ ")") themes maybe_mathjax_url +++ + headHtml (doctitle ++ " (" ++ indexName ch ++ ")") themes maybe_mathjax_url Nothing +++ bodyHtml doctitle Nothing maybe_source_url maybe_wiki_url maybe_contents_url Nothing << [ @@ -541,11 +606,11 @@ ppHtmlIndex odir doctitle _maybe_package themes ppHtmlModule :: FilePath -> String -> Themes - -> Maybe String -> SourceURLs -> WikiURLs + -> Maybe String -> SourceURLs -> WikiURLs -> BaseURL -> Maybe String -> Maybe String -> Bool -> Maybe Package -> QualOption -> Bool -> Interface -> IO () ppHtmlModule odir doctitle themes - maybe_mathjax_url maybe_source_url maybe_wiki_url + maybe_mathjax_url maybe_source_url maybe_wiki_url maybe_base_url maybe_contents_url maybe_index_url unicode pkg qual debug iface = do let mdl = ifaceMod iface @@ -563,7 +628,7 @@ ppHtmlModule odir doctitle themes = toHtml mdl_str real_qual = makeModuleQual qual aliases mdl html = - headHtml mdl_str_annot themes maybe_mathjax_url +++ + headHtml mdl_str_annot themes maybe_mathjax_url maybe_base_url +++ bodyHtml doctitle (Just iface) maybe_source_url maybe_wiki_url maybe_contents_url maybe_index_url << [ diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs b/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs index b1d64acd..08ef747a 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs @@ -17,6 +17,7 @@ module Haddock.Backends.Xhtml.Themes ( where import Haddock.Options +import Haddock.Backends.Xhtml.Types ( BaseURL, withBaseURL ) import Control.Monad (liftM) import Data.Char (toLower) @@ -176,13 +177,13 @@ cssFiles :: Themes -> [String] cssFiles ts = nub $ concatMap themeFiles ts -styleSheet :: Themes -> Html -styleSheet ts = toHtml $ zipWith mkLink rels ts +styleSheet :: BaseURL -> Themes -> Html +styleSheet base_url ts = toHtml $ zipWith mkLink rels ts where rels = "stylesheet" : repeat "alternate stylesheet" mkLink aRel t = thelink - ! [ href (themeHref t), rel aRel, thetype "text/css", + ! [ href (withBaseURL base_url (themeHref t)), rel aRel, thetype "text/css", XHtml.title (themeName t) ] << noHtml diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Types.hs b/haddock-api/src/Haddock/Backends/Xhtml/Types.hs index e3fd2d5a..a68cb559 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Types.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Types.hs @@ -12,6 +12,8 @@ ----------------------------------------------------------------------------- module Haddock.Backends.Xhtml.Types ( SourceURLs, WikiURLs, + BaseURL, + withBaseURL, LinksInfo, Splice, Unicode, @@ -20,12 +22,21 @@ module Haddock.Backends.Xhtml.Types ( import Data.Map import GHC +import qualified System.FilePath as FilePath -- the base, module and entity URLs for the source code and wiki links. type SourceURLs = (Maybe FilePath, Maybe FilePath, Map Unit FilePath, Map Unit FilePath) type WikiURLs = (Maybe FilePath, Maybe FilePath, Maybe FilePath) +-- | base url for loading js, json, css resources. The default is "." +-- +type BaseURL = Maybe String + +-- TODO: we shouldn't use 'FilePath.' +withBaseURL :: BaseURL -> String -> String +withBaseURL Nothing uri = uri +withBaseURL (Just baseUrl) uri = baseUrl FilePath. uri -- The URL for source and wiki links type LinksInfo = (SourceURLs, WikiURLs) diff --git a/haddock-api/src/Haddock/Options.hs b/haddock-api/src/Haddock/Options.hs index 4d22505f..aa10b5b3 100644 --- a/haddock-api/src/Haddock/Options.hs +++ b/haddock-api/src/Haddock/Options.hs @@ -24,6 +24,7 @@ module Haddock.Options ( optSourceCssFile, sourceUrls, wikiUrls, + baseUrl, optParCount, optDumpInterfaceFile, optShowInterfaceFile, @@ -72,6 +73,7 @@ data Flag | Flag_SourceEntityURL String | Flag_SourceLEntityURL String | Flag_WikiBaseURL String + | Flag_BaseURL String | Flag_WikiModuleURL String | Flag_WikiEntityURL String | Flag_LaTeX @@ -157,6 +159,8 @@ options backwardsCompat = "URL for a source code link for each entity.\nUsed if name links are unavailable, eg. for TH splices.", Option [] ["comments-base"] (ReqArg Flag_WikiBaseURL "URL") "URL for a comments link on the contents\nand index pages", + Option [] ["base-url"] (ReqArg Flag_BaseURL "URL") + "Base URL for static assets (eg. css, javascript, json files etc.).\nWhen given statis assets will not be copied.", Option [] ["comments-module"] (ReqArg Flag_WikiModuleURL "URL") "URL for a comments link for each module\n(using the %{MODULE} var)", Option [] ["comments-entity"] (ReqArg Flag_WikiEntityURL "URL") @@ -301,6 +305,9 @@ wikiUrls flags = ,optLast [str | Flag_WikiEntityURL str <- flags]) +baseUrl :: [Flag] -> Maybe String +baseUrl flags = optLast [str | Flag_BaseURL str <- flags] + optDumpInterfaceFile :: [Flag] -> Maybe FilePath optDumpInterfaceFile flags = optLast [ str | Flag_DumpInterface str <- flags ] diff --git a/haddock-api/src/Haddock/Utils/Json.hs b/haddock-api/src/Haddock/Utils/Json.hs index 2270a547..d5d5ae02 100644 --- a/haddock-api/src/Haddock/Utils/Json.hs +++ b/haddock-api/src/Haddock/Utils/Json.hs @@ -1,4 +1,6 @@ +{-# LANGUAGE ExplicitForAll #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} -- | Minimal JSON / RFC 7159 support -- @@ -12,35 +14,53 @@ module Haddock.Utils.Json , encodeToString , encodeToBuilder , ToJSON(toJSON) + + , Parser(..) + , Result(..) + , FromJSON(parseJSON) + , withObject + , withArray + , withString + , withDouble + , withBool + , fromJSON + , parse + , parseEither + , (.:) + , (.:?) + , decode + , decodeWith + , eitherDecode + , eitherDecodeWith + , decodeFile + , eitherDecodeFile ) where +import Control.Applicative (Alternative (..)) +import Control.Monad (MonadPlus (..), zipWithM, (>=>)) +import qualified Control.Monad as Monad +import qualified Control.Monad.Fail as Fail + +import qualified Data.ByteString.Lazy as BSL +import Data.ByteString.Builder (Builder) +import qualified Data.ByteString.Builder as BB import Data.Char import Data.Int -import Data.String import Data.Word import Data.List (intersperse) import Data.Monoid -import Data.ByteString.Builder (Builder) -import qualified Data.ByteString.Builder as BB +import GHC.Natural -- TODO: We may want to replace 'String' with 'Text' or 'ByteString' --- | A JSON value represented as a Haskell value. -data Value = Object !Object - | Array [Value] - | String String - | Number !Double - | Bool !Bool - | Null - deriving (Eq, Read, Show) +import qualified Text.Parsec.ByteString.Lazy as Parsec.Lazy +import qualified Text.ParserCombinators.Parsec as Parsec --- | A key\/value pair for an 'Object' -type Pair = (String, Value) +import Haddock.Utils.Json.Types +import Haddock.Utils.Json.Parser --- | A JSON \"object\" (key/value map). -type Object = [Pair] infixr 8 .= @@ -48,13 +68,6 @@ infixr 8 .= (.=) :: ToJSON v => String -> v -> Pair k .= v = (k, toJSON v) --- | Create a 'Value' from a list of name\/value 'Pair's. -object :: [Pair] -> Value -object = Object - -instance IsString Value where - fromString = String - -- | A type that can be converted to JSON. class ToJSON a where @@ -223,3 +236,324 @@ escapeString s -- unescaped = %x20-21 / %x23-5B / %x5D-10FFFF needsEscape c = ord c < 0x20 || c `elem` ['\\','"'] + +------------------------------------------------------------------------------ +-- FromJSON + +-- | Elements of a JSON path used to describe the location of an +-- error. +data JSONPathElement + = Key String + -- ^ JSON path element of a key into an object, + -- \"object.key\". + | Index !Int + -- ^ JSON path element of an index into an + -- array, \"array[index]\". + deriving (Eq, Show, Ord) + +type JSONPath = [JSONPathElement] + +-- | Failure continuation. +type Failure f r = JSONPath -> String -> f r + +-- | Success continuation. +type Success a f r = a -> f r + +newtype Parser a = Parser { + runParser :: forall f r. + JSONPath + -> Failure f r + -> Success a f r + -> f r + } + +modifyFailure :: (String -> String) -> Parser a -> Parser a +modifyFailure f (Parser p) = Parser $ \path kf ks -> + p path (\p' m -> kf p' (f m)) ks + +prependFailure :: String -> Parser a -> Parser a +prependFailure = modifyFailure . (++) + +prependContext :: String -> Parser a -> Parser a +prependContext name = prependFailure ("parsing " ++ name ++ " failed, ") + +typeMismatch :: String -> Value -> Parser a +typeMismatch expected actual = + fail $ "expected " ++ expected ++ ", but encountered " ++ typeOf actual + +instance Monad.Monad Parser where + m >>= g = Parser $ \path kf ks -> + runParser m path kf + (\a -> runParser (g a) path kf ks) + return = pure + +instance Fail.MonadFail Parser where + fail msg = Parser $ \path kf _ks -> kf (reverse path) msg + +instance Functor Parser where + fmap f m = Parser $ \path kf ks -> + let ks' a = ks (f a) + in runParser m path kf ks' + +instance Applicative Parser where + pure a = Parser $ \_path _kf ks -> ks a + (<*>) = apP + +instance Alternative Parser where + empty = fail "empty" + (<|>) = mplus + +instance MonadPlus Parser where + mzero = fail "mzero" + mplus a b = Parser $ \path kf ks -> + runParser a path (\_ _ -> runParser b path kf ks) ks + +instance Semigroup (Parser a) where + (<>) = mplus + +instance Monoid (Parser a) where + mempty = fail "mempty" + mappend = (<>) + +apP :: Parser (a -> b) -> Parser a -> Parser b +apP d e = do + b <- d + b <$> e + +() :: Parser a -> JSONPathElement -> Parser a +p pathElem = Parser $ \path kf ks -> runParser p (pathElem:path) kf ks + +parseIndexedJSON :: (Value -> Parser a) -> Int -> Value -> Parser a +parseIndexedJSON p idx value = p value Index idx + +unexpected :: Value -> Parser a +unexpected actual = fail $ "unexpected " ++ typeOf actual + +withObject :: String -> (Object -> Parser a) -> Value -> Parser a +withObject _ f (Object obj) = f obj +withObject name _ v = prependContext name (typeMismatch "Object" v) + +withArray :: String -> ([Value] -> Parser a) -> Value -> Parser a +withArray _ f (Array arr) = f arr +withArray name _ v = prependContext name (typeMismatch "Array" v) + +withString :: String -> (String -> Parser a) -> Value -> Parser a +withString _ f (String txt) = f txt +withString name _ v = prependContext name (typeMismatch "String" v) + +withDouble :: String -> (Double -> Parser a) -> Value -> Parser a +withDouble _ f (Number duble) = f duble +withDouble name _ v = prependContext name (typeMismatch "Number" v) + +withBool :: String -> (Bool -> Parser a) -> Value -> Parser a +withBool _ f (Bool arr) = f arr +withBool name _ v = prependContext name (typeMismatch "Boolean" v) + +class FromJSON a where + parseJSON :: Value -> Parser a + + parseJSONList :: Value -> Parser [a] + parseJSONList = withArray "[]" (zipWithM (parseIndexedJSON parseJSON) [0..]) + +instance FromJSON Bool where + parseJSON (Bool b) = pure b + parseJSON v = typeMismatch "Bool" v + +instance FromJSON () where + parseJSON = + withArray "()" $ \v -> + if null v + then pure () + else prependContext "()" $ fail "expected an empty array" + +instance FromJSON Char where + parseJSON = withString "Char" parseChar + + parseJSONList (String s) = pure s + parseJSONList v = typeMismatch "String" v + +parseChar :: String -> Parser Char +parseChar t = + if length t == 1 + then pure $ head t + else prependContext "Char" $ fail "expected a string of length 1" + +parseRealFloat :: RealFloat a => String -> Value -> Parser a +parseRealFloat _ (Number s) = pure $ realToFrac s +parseRealFloat _ Null = pure (0/0) +parseRealFloat name v = prependContext name (unexpected v) + +instance FromJSON Double where + parseJSON = parseRealFloat "Double" + +instance FromJSON Float where + parseJSON = parseRealFloat "Float" + +parseNatural :: Integer -> Parser Natural +parseNatural integer = + if integer < 0 then + fail $ "parsing Natural failed, unexpected negative number " <> show integer + else + pure $ fromIntegral integer + +parseIntegralFromDouble :: Integral a => Double -> Parser a +parseIntegralFromDouble d = + let r = toRational d + x = truncate r + in if toRational x == r + then pure $ x + else fail $ "unexpected floating number " <> show d + +parseIntegral :: Integral a => String -> Value -> Parser a +parseIntegral name = withDouble name parseIntegralFromDouble + +instance FromJSON Integer where + parseJSON = parseIntegral "Integer" + +instance FromJSON Natural where + parseJSON = withDouble "Natural" + (parseIntegralFromDouble >=> parseNatural) + +instance FromJSON Int where + parseJSON = parseIntegral "Int" + +instance FromJSON Int8 where + parseJSON = parseIntegral "Int8" + +instance FromJSON Int16 where + parseJSON = parseIntegral "Int16" + +instance FromJSON Int32 where + parseJSON = parseIntegral "Int32" + +instance FromJSON Int64 where + parseJSON = parseIntegral "Int64" + +instance FromJSON Word where + parseJSON = parseIntegral "Word" + +instance FromJSON Word8 where + parseJSON = parseIntegral "Word8" + +instance FromJSON Word16 where + parseJSON = parseIntegral "Word16" + +instance FromJSON Word32 where + parseJSON = parseIntegral "Word32" + +instance FromJSON Word64 where + parseJSON = parseIntegral "Word64" + +instance FromJSON a => FromJSON [a] where + parseJSON = parseJSONList + +data Result a = Error String + | Success a + deriving (Eq, Show) + +fromJSON :: FromJSON a => Value -> Result a +fromJSON = parse parseJSON + +parse :: (a -> Parser b) -> a -> Result b +parse m v = runParser (m v) [] (const Error) Success + +parseEither :: (a -> Parser b) -> a -> Either String b +parseEither m v = runParser (m v) [] onError Right + where onError path msg = Left (formatError path msg) + +formatError :: JSONPath -> String -> String +formatError path msg = "Error in " ++ formatPath path ++ ": " ++ msg + +formatPath :: JSONPath -> String +formatPath path = "$" ++ formatRelativePath path + +formatRelativePath :: JSONPath -> String +formatRelativePath path = format "" path + where + format :: String -> JSONPath -> String + format pfx [] = pfx + format pfx (Index idx:parts) = format (pfx ++ "[" ++ show idx ++ "]") parts + format pfx (Key key:parts) = format (pfx ++ formatKey key) parts + + formatKey :: String -> String + formatKey key + | isIdentifierKey key = "." ++ key + | otherwise = "['" ++ escapeKey key ++ "']" + + isIdentifierKey :: String -> Bool + isIdentifierKey [] = False + isIdentifierKey (x:xs) = isAlpha x && all isAlphaNum xs + + escapeKey :: String -> String + escapeKey = concatMap escapeChar + + escapeChar :: Char -> String + escapeChar '\'' = "\\'" + escapeChar '\\' = "\\\\" + escapeChar c = [c] + +explicitParseField :: (Value -> Parser a) -> Object -> String -> Parser a +explicitParseField p obj key = + case key `lookup` obj of + Nothing -> fail $ "key " ++ key ++ " not found" + Just v -> p v Key key + +(.:) :: FromJSON a => Object -> String -> Parser a +(.:) = explicitParseField parseJSON + +explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> String -> Parser (Maybe a) +explicitParseFieldMaybe p obj key = + case key `lookup` obj of + Nothing -> pure Nothing + Just v -> Just <$> p v Key key + +(.:?) :: FromJSON a => Object -> String -> Parser (Maybe a) +(.:?) = explicitParseFieldMaybe parseJSON + + +decodeWith :: (Value -> Result a) -> BSL.ByteString -> Maybe a +decodeWith decoder bsl = + case Parsec.parse parseJSONValue "" bsl of + Left _ -> Nothing + Right json -> + case decoder json of + Success a -> Just a + Error _ -> Nothing + +decode :: FromJSON a => BSL.ByteString -> Maybe a +decode = decodeWith fromJSON + +eitherDecodeWith :: (Value -> Result a) -> BSL.ByteString -> Either String a +eitherDecodeWith decoder bsl = + case Parsec.parse parseJSONValue "" bsl of + Left parsecError -> Left (show parsecError) + Right json -> + case decoder json of + Success a -> Right a + Error err -> Left err + +eitherDecode :: FromJSON a => BSL.ByteString -> Either String a +eitherDecode = eitherDecodeWith fromJSON + + +decodeFile :: FromJSON a => FilePath -> IO (Maybe a) +decodeFile filePath = do + parsecResult <- Parsec.Lazy.parseFromFile parseJSONValue filePath + case parsecResult of + Right r -> + case fromJSON r of + Success a -> return (Just a) + Error _ -> return Nothing + Left _ -> return Nothing + + +eitherDecodeFile :: FromJSON a => FilePath -> IO (Either String a) +eitherDecodeFile filePath = do + parsecResult <- Parsec.Lazy.parseFromFile parseJSONValue filePath + case parsecResult of + Right r -> + case fromJSON r of + Success a -> return (Right a) + Error err -> return (Left err) + Left err -> return $ Left (show err) + diff --git a/haddock-api/src/Haddock/Utils/Json/Parser.hs b/haddock-api/src/Haddock/Utils/Json/Parser.hs new file mode 100644 index 00000000..018e27d3 --- /dev/null +++ b/haddock-api/src/Haddock/Utils/Json/Parser.hs @@ -0,0 +1,102 @@ +-- | Json "Parsec" parser, based on +-- [json](https://hackage.haskell.org/package/json) package. +-- +module Haddock.Utils.Json.Parser + ( parseJSONValue + ) where + +import Prelude hiding (null) + +import Control.Applicative (Alternative (..)) +import Control.Monad (MonadPlus (..)) +import Data.Char (isHexDigit) +import Data.Functor (($>)) +import qualified Data.ByteString.Lazy.Char8 as BSCL +import Numeric +import Text.Parsec.ByteString.Lazy (Parser) +import Text.ParserCombinators.Parsec (()) +import qualified Text.ParserCombinators.Parsec as Parsec + +import Haddock.Utils.Json.Types hiding (object) + +parseJSONValue :: Parser Value +parseJSONValue = Parsec.spaces *> parseValue + +tok :: Parser a -> Parser a +tok p = p <* Parsec.spaces + +parseValue :: Parser Value +parseValue = + parseNull + <|> Bool <$> parseBoolean + <|> Array <$> parseArray + <|> String <$> parseString + <|> Object <$> parseObject + <|> Number <$> parseNumber + "JSON value" + +parseNull :: Parser Value +parseNull = tok + $ Parsec.string "null" + $> Null + +parseBoolean :: Parser Bool +parseBoolean = tok + $ Parsec.string "true" $> True + <|> Parsec.string "false" $> False + +parseArray :: Parser [Value] +parseArray = + Parsec.between + (tok (Parsec.char '[')) + (tok (Parsec.char ']')) + (parseValue `Parsec.sepBy` tok (Parsec.char ',')) + +parseString :: Parser String +parseString = + Parsec.between + (tok (Parsec.char '"')) + (tok (Parsec.char '"')) + (many char) + where + char = (Parsec.char '\\' >> escapedChar) + <|> Parsec.satisfy (\x -> x /= '"' && x /= '\\') + + escapedChar = + Parsec.char '"' $> '"' + <|> Parsec.char '\\' $> '\\' + <|> Parsec.char '/' $> '/' + <|> Parsec.char 'b' $> '\b' + <|> Parsec.char 'f' $> '\f' + <|> Parsec.char 'n' $> '\n' + <|> Parsec.char 'r' $> '\r' + <|> Parsec.char 't' $> '\t' + <|> Parsec.char 'u' *> uni + "escape character" + + uni = check =<< Parsec.count 4 (Parsec.satisfy isHexDigit) + where + check x | code <= max_char = return (toEnum code) + | otherwise = mzero + where code = fst $ head $ readHex x + max_char = fromEnum (maxBound :: Char) + +parseObject :: Parser Object +parseObject = + Parsec.between + (tok (Parsec.char '{')) + (tok (Parsec.char '}')) + (field `Parsec.sepBy` tok (Parsec.char ',')) + where + field :: Parser (String, Value) + field = (,) + <$> parseString + <* tok (Parsec.char ':') + <*> parseValue + +parseNumber :: Parser Double +parseNumber = tok $ do + s <- BSCL.unpack <$> Parsec.getInput + case readSigned readFloat s of + [(n,s')] -> Parsec.setInput (BSCL.pack s') $> n + _ -> mzero diff --git a/haddock-api/src/Haddock/Utils/Json/Types.hs b/haddock-api/src/Haddock/Utils/Json/Types.hs new file mode 100644 index 00000000..1174329c --- /dev/null +++ b/haddock-api/src/Haddock/Utils/Json/Types.hs @@ -0,0 +1,42 @@ +module Haddock.Utils.Json.Types + ( Value(..) + , typeOf + , Pair + , Object + , object + ) where + +import Data.String + +-- TODO: We may want to replace 'String' with 'Text' or 'ByteString' + +-- | A JSON value represented as a Haskell value. +data Value = Object !Object + | Array [Value] + | String String + | Number !Double + | Bool !Bool + | Null + deriving (Eq, Read, Show) + +typeOf :: Value -> String +typeOf v = case v of + Object _ -> "Object" + Array _ -> "Array" + String _ -> "String" + Number _ -> "Number" + Bool _ -> "Boolean" + Null -> "Null" + +-- | A key\/value pair for an 'Object' +type Pair = (String, Value) + +-- | A JSON \"object\" (key/value map). +type Object = [Pair] + +-- | Create a 'Value' from a list of name\/value 'Pair's. +object :: [Pair] -> Value +object = Object + +instance IsString Value where + fromString = String diff --git a/haddock.cabal b/haddock.cabal index 65e1aa6b..dfb4e9a9 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -111,6 +111,8 @@ executable haddock Haddock.Parser Haddock.Utils Haddock.Utils.Json + Haddock.Utils.Json.Parser + Haddock.Utils.Json.Types Haddock.Backends.Xhtml Haddock.Backends.Xhtml.Decl Haddock.Backends.Xhtml.DocMarkup -- cgit v1.2.3 From a33e376531a4f478bacd41fc3028985405b8c164 Mon Sep 17 00:00:00 2001 From: wz1000 Date: Mon, 11 Oct 2021 15:40:19 +0530 Subject: Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC --- haddock-api/src/Haddock/Backends/Hyperlinker.hs | 12 +++++- haddock-api/src/Haddock/Interface.hs | 54 +++++++++++++++++++++++-- haddock-test/src/Test/Haddock/Xhtml.hs | 3 +- html-test/ref/Bug1004.html | 12 +++--- html-test/ref/BundledPatterns.html | 8 ++-- html-test/ref/BundledPatterns2.html | 8 ++-- 6 files changed, 76 insertions(+), 21 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs index 39be6762..68e03fd5 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs @@ -22,7 +22,7 @@ import System.FilePath import GHC.Iface.Ext.Types ( pattern HiePath, HieFile(..), HieASTs(..), HieAST(..), SourcedNodeInfo(..) ) import GHC.Iface.Ext.Binary ( readHieFile, hie_file_result ) -import GHC.Types.SrcLoc ( realSrcLocSpan, mkRealSrcLoc ) +import GHC.Types.SrcLoc ( realSrcLocSpan, mkRealSrcLoc, srcSpanFile ) import Data.Map as M import GHC.Data.FastString ( mkFastString ) import GHC.Unit.Module ( Module, moduleName ) @@ -71,7 +71,7 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = case ifaceHieFile let fileFs = mkFastString file mast | M.size asts == 1 = snd <$> M.lookupMin asts | otherwise = M.lookup (HiePath (mkFastString file)) asts - tokens = parse df file rawSrc + tokens' = parse df file rawSrc ast = fromMaybe (emptyHieAst fileFs) mast fullAst = recoverFullIfaceTypes df types ast @@ -81,6 +81,14 @@ ppHyperlinkedModuleSource verbosity srcdir pretty srcs iface = case ifaceHieFile else out verbosity verbose $ unwords [ "couldn't find ast for" , file, show (M.keys asts) ] + -- The C preprocessor can double the backslashes on tokens (see #19236), + -- which means the source spans will not be comparable and we will not + -- be able to associate the HieAST with the correct tokens. + -- + -- We work around this by setting the source span of the tokens to the file + -- name from the HieAST + let tokens = fmap (\tk -> tk {tkSpan = (tkSpan tk){srcSpanFile = srcSpanFile $ nodeSpan fullAst}}) tokens' + -- Produce and write out the hyperlinked sources writeUtf8File path . renderToString pretty . render' fullAst $ tokens Nothing -> return () diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 2e9b2f7e..ba7d9d30 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -55,7 +55,7 @@ import qualified Data.Set as Set import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) -import GHC.Data.Graph.Directed (flattenSCCs) +import GHC.Data.Graph.Directed import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) @@ -68,7 +68,7 @@ import GHC.Types.Name (nameIsFromExternalPackage, nameOccName) import GHC.Types.Name.Occurrence (isTcOcc) import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK) import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet) -import GHC.Unit.Module.Graph (ModuleGraphNode (..)) +import GHC.Unit.Module.Graph import GHC.Unit.Module.ModSummary (emsModSummary, isBootSummary) import GHC.Unit.Types (IsBootInterface (..)) import GHC.Utils.Error (withTiming) @@ -170,13 +170,59 @@ createIfaces verbosity modules flags instIfaceMap = do moduleSet <- liftIO getModules let + -- We topologically sort the module graph including boot files, + -- so it should be acylic (hopefully we failed much earlier if this is not the case) + -- We then filter out boot modules from the resultant topological sort + -- + -- We do it this way to make 'buildHomeLinks' a bit more stable + -- 'buildHomeLinks' depends on the topological order of its input in order + -- to construct its result. In particular, modules closer to the bottom of + -- the dependency chain are to be prefered for link destinations. + -- + -- If there are cycles in the graph, then this order is indeterminate + -- (the nodes in the cycle can be ordered in any way). + -- While 'topSortModuleGraph' does guarantee stability for equivalent + -- module graphs, seemingly small changes in the ModuleGraph can have + -- big impacts on the `LinkEnv` constructed. + -- + -- For example, suppose + -- G1 = A.hs -> B.hs -> C.hs (where '->' denotes an import). + -- + -- Then suppose C.hs is changed to have a cyclic dependency on A + -- + -- G2 = A.hs -> B.hs -> C.hs -> A.hs-boot + -- + -- For G1, `C.hs` is preferred for link destinations. However, for G2, + -- the topologically sorted order not taking into account boot files (so + -- C -> A) is completely indeterminate. + -- Using boot files to resolve cycles, we end up with the original order + -- [C, B, A] (in decreasing order of preference for links) + -- + -- This exact case came up in testing for the 'base' package, where there + -- is a big module cycle involving 'Prelude' on windows, but the cycle doesn't + -- include 'Prelude' on non-windows platforms. This lead to drastically different + -- LinkEnv's (and failing haddockHtmlTests) across the platforms + -- + -- In effect, for haddock users this behaviour (using boot files to eliminate cycles) + -- means that {-# SOURCE #-} imports no longer count towards re-ordering + -- the preference of modules for linking. + -- + -- i.e. if module A imports B, then B is preferred over A, + -- but if module A {-# SOURCE #-} imports B, then we can't say the same. + -- + go (AcyclicSCC (ModuleNode ems)) + | NotBoot <- isBootSummary (emsModSummary ems) = [ems] + | otherwise = [] + go (AcyclicSCC _) = [] + go (CyclicSCC _) = error "haddock: module graph cyclic even with boot files" + ifaces :: [Interface] ifaces = [ Map.findWithDefault (error "haddock:iface") (ms_mod (emsModSummary ems)) ifaceMap - | ModuleNode ems <- flattenSCCs $ topSortModuleGraph True modGraph Nothing + | ems <- concatMap go $ topSortModuleGraph False modGraph Nothing ] return (ifaces, moduleSet) @@ -352,7 +398,7 @@ processModule1 verbosity flags ifaces inst_ifaces hsc_env mod_summary tc_gbl_env -- The interfaces are passed in in topologically sorted order, but we start -- by reversing the list so we can do a foldl. buildHomeLinks :: [Interface] -> LinkEnv -buildHomeLinks ifaces = foldl upd Map.empty (reverse ifaces) +buildHomeLinks ifaces = foldl' upd Map.empty (reverse ifaces) where upd old_env iface | OptHide `elem` ifaceOptions iface = old_env diff --git a/haddock-test/src/Test/Haddock/Xhtml.hs b/haddock-test/src/Test/Haddock/Xhtml.hs index bca2c4cc..74d8c4f7 100644 --- a/haddock-test/src/Test/Haddock/Xhtml.hs +++ b/haddock-test/src/Test/Haddock/Xhtml.hs @@ -23,8 +23,9 @@ import Data.Char ( isSpace ) newtype Xml = Xml { unXml :: String } -- | Part of parsing involves dropping the @DOCTYPE@ line +-- and windows newline endings parseXml :: String -> Maybe Xml -parseXml = Just . Xml . dropDocTypeLine +parseXml = Just . Xml . filter (/= '\r') . dropDocTypeLine where dropDocTypeLine bs | " ( (Typeable a, a, Typeable f, f, Typeable g, g, Typeable k, Data

    dataCast1 :: :: Typeable t => (forall

    dataCast2 :: :: Typeable t => (foralldata Vec :: :: Nat -> * -> * wheredata RTree :: :: Nat -> * -> * wheredata Vec :: :: Nat -> * -> * wheredata RTree :: :: Nat -> * -> * wheredata Vec :: :: Nat -> * -> * wheredata RTree :: :: Nat -> * -> * wheredata Vec :: :: Nat -> * -> * wheredata RTree :: :: Nat -> * -> * where Date: Fri, 15 Oct 2021 22:19:42 +0200 Subject: update haddockHypsrcTest for GHC MR !6705 (#1430) --- hypsrc-test/ref/src/Classes.html | 3 +++ hypsrc-test/ref/src/Constructors.html | 1 + hypsrc-test/ref/src/Quasiquoter.html | 2 ++ 3 files changed, 6 insertions(+) diff --git a/hypsrc-test/ref/src/Classes.html b/hypsrc-test/ref/src/Classes.html index 16d3b333..4b0343cf 100644 --- a/hypsrc-test/ref/src/Classes.html +++ b/hypsrc-test/ref/src/Classes.html @@ -342,6 +342,7 @@ forall a. a -> a >[a] -> Int +forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int [Int] -> Int +forall a. Num a => [a] -> a forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a [Int] -> Int +forall a. Num a => [a] -> a forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a [Int] -> Int +forall a. Num a => [a] -> a forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a Exp -> Q Exp +forall a. a -> Q a forall (f :: * -> *) a. Applicative f => a -> f a String -> Q a +forall a. String -> Q a forall (m :: * -> *) a. MonadFail m => String -> m a Date: Fri, 15 Oct 2021 22:20:10 +0200 Subject: Fix after PkgQual refactoring (#1429) --- haddock-api/src/Haddock/Interface/Create.hs | 17 +++++++---------- 1 file changed, 7 insertions(+), 10 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 2782f711..75789a06 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -59,7 +59,6 @@ import GHC.Data.FastString (bytesFS, unpackFS) import GHC.Driver.Ppr (showSDoc) import GHC.HsToCore.Docs hiding (mkMaps) import GHC.IORef (readIORef) -import GHC.Parser.Annotation (IsUnicodeSyntax (..)) import GHC.Stack (HasCallStack) import GHC.Tc.Types hiding (IfM) import GHC.Tc.Utils.Monad (finalSafeMode) @@ -72,14 +71,13 @@ import GHC.Types.Name.Reader (GlobalRdrEnv, greMangledName, lookupGlobalRdrEnv) import GHC.Types.Name.Set (elemNameSet, mkNameSet) import GHC.Types.SourceFile (HscSource (..)) import GHC.Types.SourceText (SourceText (..), sl_fs) +import GHC.Unit.Types import qualified GHC.Types.SrcLoc as SrcLoc import qualified GHC.Unit.Module as Module import GHC.Unit.Module.ModSummary (msHsFilePath) -import GHC.Unit.Module.Warnings (WarningTxt (..), Warnings (..)) import GHC.Unit.State (PackageName (..), UnitState, lookupModuleInAllUnits) import qualified GHC.Utils.Outputable as O import GHC.Utils.Panic (pprPanic) -import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Unit.Module.Warnings newtype IfEnv m = IfEnv @@ -351,8 +349,7 @@ mkAliasMap state impDecls = -- them to the user. We should reuse that information; -- or at least reuse the renamed imports, which know what -- they import! - (fmap Module.fsToUnit $ - fmap sl_fs $ ideclPkgQual impDecl) + (ideclPkgQual impDecl) (case ideclName impDecl of SrcLoc.L _ name -> name), alias)) impDecls @@ -395,11 +392,11 @@ unrestrictedModuleImports idecls = -- Similar to GHC.lookupModule -- ezyang: Not really... lookupModuleDyn :: - UnitState -> Maybe Unit -> ModuleName -> Module -lookupModuleDyn _ (Just pkgId) mdlName = - Module.mkModule pkgId mdlName -lookupModuleDyn state Nothing mdlName = - case lookupModuleInAllUnits state mdlName of + UnitState -> PkgQual -> ModuleName -> Module +lookupModuleDyn state pkg_qual mdlName = case pkg_qual of + OtherPkg uid -> Module.mkModule (RealUnit (Definite uid)) mdlName + ThisPkg uid -> Module.mkModule (RealUnit (Definite uid)) mdlName + NoPkgQual -> case lookupModuleInAllUnits state mdlName of (m,_):_ -> m [] -> Module.mkModule Module.mainUnit mdlName -- cgit v1.2.3 From 1ef24e617651955f07c4fb6f2d488806cc6785ec Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Thu, 28 Oct 2021 18:57:10 +0100 Subject: Update for changes in GHC for branch wip/az/no-srcspan-anno-instances --- haddock-api/src/Haddock/Convert.hs | 12 ++++++------ haddock-api/src/Haddock/Interface/Create.hs | 4 ++-- haddock-api/src/Haddock/Types.hs | 8 ++++---- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index cf533c20..29e0957b 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -341,14 +341,14 @@ synifyInjectivityAnn Nothing _ _ = Nothing synifyInjectivityAnn _ _ NotInjective = Nothing synifyInjectivityAnn (Just lhs) tvs (Injective inj) = let rhs = map (noLocA . tyVarName) (filterByList inj tvs) - in Just $ noLoc $ InjectivityAnn noAnn (noLocA lhs) rhs + in Just $ noLocA $ InjectivityAnn noAnn (noLocA lhs) rhs synifyFamilyResultSig :: Maybe Name -> Kind -> LFamilyResultSig GhcRn synifyFamilyResultSig Nothing kind - | isLiftedTypeKind kind = noLoc $ NoSig noExtField - | otherwise = noLoc $ KindSig noExtField (synifyKindSig kind) + | isLiftedTypeKind kind = noLocA $ NoSig noExtField + | otherwise = noLocA $ KindSig noExtField (synifyKindSig kind) synifyFamilyResultSig (Just name) kind = - noLoc $ TyVarSig noExtField (noLocA $ KindedTyVar noAnn () (noLocA name) (synifyKindSig kind)) + noLocA $ TyVarSig noExtField (noLocA $ KindedTyVar noAnn () (noLocA name) (synifyKindSig kind)) -- User beware: it is your responsibility to pass True (use_gadt_syntax) -- for any constructor that would be misrepresented by omitting its @@ -387,7 +387,7 @@ synifyDataCon use_gadt_syntax dc = field_tys = zipWith con_decl_field (dataConFieldLabels dc) linear_tys con_decl_field fl synTy = noLocA $ - ConDeclField noAnn [noLoc $ FieldOcc (flSelector fl) (noLocA $ mkVarUnqual $ flLabel fl)] synTy + ConDeclField noAnn [noLocA $ FieldOcc (flSelector fl) (noLocA $ mkVarUnqual $ flLabel fl)] synTy Nothing mk_h98_arg_tys :: Either ErrMsg (HsConDeclH98Details GhcRn) @@ -611,7 +611,7 @@ synifyType _ vs (TyConApp tc tys) | tc `hasKey` ipClassKey , [name, ty] <- tys , Just x <- isStrLitTy name - = noLocA $ HsIParamTy noAnn (noLoc $ HsIPName x) (synifyType WithinType vs ty) + = noLocA $ HsIParamTy noAnn (noLocA $ HsIPName x) (synifyType WithinType vs ty) -- and equalities | tc `hasKey` eqTyConKey , [ty1, ty2] <- tys diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 75789a06..4d746405 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1170,8 +1170,8 @@ extractRecSel nm t tvs (L _ con : rest) = _ -> extractRecSel nm t tvs rest where matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)] - matching_fields flds = [ (l,f) | f@(L _ (ConDeclField _ ns _ _)) <- flds - , L l n <- ns, foExt n == nm ] + matching_fields flds = [ (locA l,f) | f@(L _ (ConDeclField _ ns _ _)) <- flds + , L l n <- ns, foExt n == nm ] data_ty -- ResTyGADT _ ty <- con_res con = ty | ConDeclGADT{} <- con = con_res_ty con diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 7c4aeb80..05375185 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -709,8 +709,8 @@ type instance Anno (HsTyVarBndr flag DocNameI) = SrcSpanAnnA type instance Anno [LocatedA (HsType DocNameI)] = SrcSpanAnnC type instance Anno (HsType DocNameI) = SrcSpanAnnA type instance Anno (DataFamInstDecl DocNameI) = SrcSpanAnnA -type instance Anno (DerivStrategy DocNameI) = SrcSpan -type instance Anno (FieldOcc DocNameI) = SrcSpan +type instance Anno (DerivStrategy DocNameI) = SrcAnn NoEpAnns +type instance Anno (FieldOcc DocNameI) = SrcAnn NoEpAnns type instance Anno (ConDeclField DocNameI) = SrcSpan type instance Anno (Located (ConDeclField DocNameI)) = SrcSpan type instance Anno [Located (ConDeclField DocNameI)] = SrcSpan @@ -720,9 +720,9 @@ type instance Anno (TyFamInstDecl DocNameI) = SrcSpanAnnA type instance Anno [LocatedA (TyFamInstDecl DocNameI)] = SrcSpanAnnL type instance Anno (FamilyDecl DocNameI) = SrcSpan type instance Anno (Sig DocNameI) = SrcSpan -type instance Anno (InjectivityAnn DocNameI) = SrcSpan +type instance Anno (InjectivityAnn DocNameI) = SrcAnn NoEpAnns type instance Anno (HsDecl DocNameI) = SrcSpanAnnA -type instance Anno (FamilyResultSig DocNameI) = SrcSpan +type instance Anno (FamilyResultSig DocNameI) = SrcAnn NoEpAnns type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA type instance Anno (HsSigType DocNameI) = SrcSpanAnnA -- cgit v1.2.3 From f7bfa0013f2bc3934a63ea7af21fe41a4e91058b Mon Sep 17 00:00:00 2001 From: Vladislav Zavialov Date: Fri, 5 Nov 2021 02:02:50 +0300 Subject: Do not use forall as an identifier See GHC ticket #20609 --- haddock-api/src/Haddock/Interface/Rename.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 98b3a6e6..98c39859 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -506,7 +506,7 @@ renameCon :: ConDecl GhcRn -> RnM (ConDecl DocNameI) renameCon decl@(ConDeclH98 { con_name = lname, con_ex_tvs = ltyvars , con_mb_cxt = lcontext, con_args = details , con_doc = mbldoc - , con_forall = forall }) = do + , con_forall = forall_ }) = do lname' <- renameL lname ltyvars' <- mapM renameLTyVarBndr ltyvars lcontext' <- traverse renameLContext lcontext @@ -514,7 +514,7 @@ renameCon decl@(ConDeclH98 { con_name = lname, con_ex_tvs = ltyvars mbldoc' <- mapM renameLDocHsSyn mbldoc return (decl { con_ext = noExtField, con_name = lname', con_ex_tvs = ltyvars' , con_mb_cxt = lcontext' - , con_forall = forall -- Remove when #18311 is fixed + , con_forall = forall_ -- Remove when #18311 is fixed , con_args = details', con_doc = mbldoc' }) renameCon ConDeclGADT { con_names = lnames, con_bndrs = bndrs -- cgit v1.2.3 From 8a73a5babd07530326f1ba06bdfe95f49f66b967 Mon Sep 17 00:00:00 2001 From: Krzysztof Gogolewski Date: Sat, 27 Nov 2021 02:42:35 +0100 Subject: Update after NoExtCon -> DataConCantHappen rename --- haddock-api/src/Haddock/GhcUtils.hs | 2 +- haddock-api/src/Haddock/Types.hs | 24 ++++++++++++------------ 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 599404a0..85e6fcf4 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -114,7 +114,7 @@ pretty = showPpr -- instantiated at DocNameI instead of (GhcPass _). -- | Like 'hsTyVarName' from GHC API, but not instantiated at (GhcPass _) -hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ NoExtCon, UnXRec n) +hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ DataConCantHappen, UnXRec n) => HsTyVarBndr flag n -> IdP n hsTyVarBndrName (UserTyVar _ _ name) = unXRec @n name hsTyVarBndrName (KindedTyVar _ _ name _) = unXRec @n name diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 05375185..30f583b0 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -319,7 +319,7 @@ type instance NoGhcTc DocNameI = DocNameI type instance IdP DocNameI = DocName instance CollectPass DocNameI where - collectXXPat _ _ ext = noExtCon ext + collectXXPat _ _ ext = dataConCantHappen ext instance NamedThing DocName where getName (Documented name _) = name @@ -760,11 +760,11 @@ type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField type instance XHsForAllInvis DocNameI = NoExtField -type instance XXHsForAllTelescope DocNameI = NoExtCon +type instance XXHsForAllTelescope DocNameI = DataConCantHappen type instance XUserTyVar DocNameI = NoExtField type instance XKindedTyVar DocNameI = NoExtField -type instance XXTyVarBndr DocNameI = NoExtCon +type instance XXTyVarBndr DocNameI = DataConCantHappen type instance XCFieldOcc DocNameI = DocName type instance XXFieldOcc DocNameI = NoExtField @@ -780,7 +780,7 @@ type instance XForeignExport DocNameI = NoExtField type instance XForeignImport DocNameI = NoExtField type instance XConDeclGADT DocNameI = NoExtField type instance XConDeclH98 DocNameI = NoExtField -type instance XXConDecl DocNameI = NoExtCon +type instance XXConDecl DocNameI = DataConCantHappen type instance XDerivD DocNameI = NoExtField type instance XInstD DocNameI = NoExtField @@ -791,10 +791,10 @@ type instance XTyClD DocNameI = NoExtField type instance XNoSig DocNameI = NoExtField type instance XCKindSig DocNameI = NoExtField type instance XTyVarSig DocNameI = NoExtField -type instance XXFamilyResultSig DocNameI = NoExtCon +type instance XXFamilyResultSig DocNameI = DataConCantHappen type instance XCFamEqn DocNameI _ = NoExtField -type instance XXFamEqn DocNameI _ = NoExtCon +type instance XXFamEqn DocNameI _ = DataConCantHappen type instance XCClsInstDecl DocNameI = NoExtField type instance XCDerivDecl DocNameI = NoExtField @@ -811,23 +811,23 @@ type instance XClassDecl DocNameI = NoExtField type instance XDataDecl DocNameI = NoExtField type instance XSynDecl DocNameI = NoExtField type instance XFamDecl DocNameI = NoExtField -type instance XXFamilyDecl DocNameI = NoExtCon -type instance XXTyClDecl DocNameI = NoExtCon +type instance XXFamilyDecl DocNameI = DataConCantHappen +type instance XXTyClDecl DocNameI = DataConCantHappen type instance XHsWC DocNameI _ = NoExtField type instance XHsOuterExplicit DocNameI _ = NoExtField type instance XHsOuterImplicit DocNameI = NoExtField -type instance XXHsOuterTyVarBndrs DocNameI = NoExtCon +type instance XXHsOuterTyVarBndrs DocNameI = DataConCantHappen type instance XHsSig DocNameI = NoExtField -type instance XXHsSigType DocNameI = NoExtCon +type instance XXHsSigType DocNameI = DataConCantHappen type instance XHsQTvs DocNameI = NoExtField type instance XConDeclField DocNameI = NoExtField -type instance XXConDeclField DocNameI = NoExtCon +type instance XXConDeclField DocNameI = DataConCantHappen -type instance XXPat DocNameI = NoExtCon +type instance XXPat DocNameI = DataConCantHappen type instance XCInjectivityAnn DocNameI = NoExtField -- cgit v1.2.3 From bbe3c508cc5688683f9febbed814e5230dce0c4b Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Thu, 2 Dec 2021 11:46:54 +0000 Subject: Update html-test for Data.List revert --- html-test/ref/Identifiers.html | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html index b177266d..76487140 100644 --- a/html-test/ref/Identifiers.html +++ b/html-test/ref/Identifiers.html @@ -147,7 +147,7 @@ >, Foldableelem

  • ++, Foldableelem, elemUnqualified: 1 `Foldable``elem` [-3..3]
  • Qualified: 1 `elem` [-3..3]
  • Namespaced: `Foldable``elem`, `elem` Date: Thu, 16 Dec 2021 09:29:51 +0100 Subject: Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski Co-authored-by: Matthew Pickering --- haddock-api/src/Haddock/GhcUtils.hs | 2 +- haddock-api/src/Haddock/Interface.hs | 14 ++++++++------ haddock-api/src/Haddock/Types.hs | 24 ++++++++++++------------ html-test/ref/Identifiers.html | 10 +++++----- 4 files changed, 26 insertions(+), 24 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 599404a0..85e6fcf4 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -114,7 +114,7 @@ pretty = showPpr -- instantiated at DocNameI instead of (GhcPass _). -- | Like 'hsTyVarName' from GHC API, but not instantiated at (GhcPass _) -hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ NoExtCon, UnXRec n) +hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ DataConCantHappen, UnXRec n) => HsTyVarBndr flag n -> IdP n hsTyVarBndrName (UserTyVar _ _ name) = unXRec @n name hsTyVarBndrName (KindedTyVar _ _ name _) = unXRec @n name diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index ba7d9d30..e4934711 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -56,11 +56,11 @@ import qualified Data.Set as Set import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed -import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) +import GHC.Driver.Env import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs (getMainDeclBinder) -import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) +import GHC.Plugins import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) @@ -145,10 +145,12 @@ createIfaces verbosity modules flags instIfaceMap = do let installHaddockPlugin :: HscEnv -> HscEnv - installHaddockPlugin hsc_env = hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) $ hsc_env - { hsc_static_plugins = - haddockPlugin : hsc_static_plugins hsc_env - } + installHaddockPlugin hsc_env = + let + old_plugins = hsc_plugins hsc_env + new_plugins = old_plugins { staticPlugins = haddockPlugin : staticPlugins old_plugins } + hsc_env' = hsc_env { hsc_plugins = new_plugins } + in hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) hsc_env' -- Note that we would rather use withTempSession but as long as we -- have the separate attachInstances step we need to keep the session diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 05375185..30f583b0 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -319,7 +319,7 @@ type instance NoGhcTc DocNameI = DocNameI type instance IdP DocNameI = DocName instance CollectPass DocNameI where - collectXXPat _ _ ext = noExtCon ext + collectXXPat _ _ ext = dataConCantHappen ext instance NamedThing DocName where getName (Documented name _) = name @@ -760,11 +760,11 @@ type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField type instance XHsForAllInvis DocNameI = NoExtField -type instance XXHsForAllTelescope DocNameI = NoExtCon +type instance XXHsForAllTelescope DocNameI = DataConCantHappen type instance XUserTyVar DocNameI = NoExtField type instance XKindedTyVar DocNameI = NoExtField -type instance XXTyVarBndr DocNameI = NoExtCon +type instance XXTyVarBndr DocNameI = DataConCantHappen type instance XCFieldOcc DocNameI = DocName type instance XXFieldOcc DocNameI = NoExtField @@ -780,7 +780,7 @@ type instance XForeignExport DocNameI = NoExtField type instance XForeignImport DocNameI = NoExtField type instance XConDeclGADT DocNameI = NoExtField type instance XConDeclH98 DocNameI = NoExtField -type instance XXConDecl DocNameI = NoExtCon +type instance XXConDecl DocNameI = DataConCantHappen type instance XDerivD DocNameI = NoExtField type instance XInstD DocNameI = NoExtField @@ -791,10 +791,10 @@ type instance XTyClD DocNameI = NoExtField type instance XNoSig DocNameI = NoExtField type instance XCKindSig DocNameI = NoExtField type instance XTyVarSig DocNameI = NoExtField -type instance XXFamilyResultSig DocNameI = NoExtCon +type instance XXFamilyResultSig DocNameI = DataConCantHappen type instance XCFamEqn DocNameI _ = NoExtField -type instance XXFamEqn DocNameI _ = NoExtCon +type instance XXFamEqn DocNameI _ = DataConCantHappen type instance XCClsInstDecl DocNameI = NoExtField type instance XCDerivDecl DocNameI = NoExtField @@ -811,23 +811,23 @@ type instance XClassDecl DocNameI = NoExtField type instance XDataDecl DocNameI = NoExtField type instance XSynDecl DocNameI = NoExtField type instance XFamDecl DocNameI = NoExtField -type instance XXFamilyDecl DocNameI = NoExtCon -type instance XXTyClDecl DocNameI = NoExtCon +type instance XXFamilyDecl DocNameI = DataConCantHappen +type instance XXTyClDecl DocNameI = DataConCantHappen type instance XHsWC DocNameI _ = NoExtField type instance XHsOuterExplicit DocNameI _ = NoExtField type instance XHsOuterImplicit DocNameI = NoExtField -type instance XXHsOuterTyVarBndrs DocNameI = NoExtCon +type instance XXHsOuterTyVarBndrs DocNameI = DataConCantHappen type instance XHsSig DocNameI = NoExtField -type instance XXHsSigType DocNameI = NoExtCon +type instance XXHsSigType DocNameI = DataConCantHappen type instance XHsQTvs DocNameI = NoExtField type instance XConDeclField DocNameI = NoExtField -type instance XXConDeclField DocNameI = NoExtCon +type instance XXConDeclField DocNameI = DataConCantHappen -type instance XXPat DocNameI = NoExtCon +type instance XXPat DocNameI = DataConCantHappen type instance XCInjectivityAnn DocNameI = NoExtField diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html index b177266d..76487140 100644 --- a/html-test/ref/Identifiers.html +++ b/html-test/ref/Identifiers.html @@ -147,7 +147,7 @@ >, Foldableelem
  • ++, Foldableelem, elemUnqualified: 1 `Foldable``elem` [-3..3]
  • Qualified: 1 `elem` [-3..3]
  • Namespaced: `Foldable``elem`, `elem` Date: Tue, 14 Dec 2021 11:28:48 +0100 Subject: Fix for new Plugins datatype --- haddock-api/src/Haddock/Interface.hs | 14 ++++++++------ 1 file changed, 8 insertions(+), 6 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index ba7d9d30..e4934711 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -56,11 +56,11 @@ import qualified Data.Set as Set import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed -import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) +import GHC.Driver.Env import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs (getMainDeclBinder) -import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) +import GHC.Plugins import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) @@ -145,10 +145,12 @@ createIfaces verbosity modules flags instIfaceMap = do let installHaddockPlugin :: HscEnv -> HscEnv - installHaddockPlugin hsc_env = hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) $ hsc_env - { hsc_static_plugins = - haddockPlugin : hsc_static_plugins hsc_env - } + installHaddockPlugin hsc_env = + let + old_plugins = hsc_plugins hsc_env + new_plugins = old_plugins { staticPlugins = haddockPlugin : staticPlugins old_plugins } + hsc_env' = hsc_env { hsc_plugins = new_plugins } + in hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) hsc_env' -- Note that we would rather use withTempSession but as long as we -- have the separate attachInstances step we need to keep the session -- cgit v1.2.3 From 5d14361971ec6e6c3dfca282e4b80b307087afe5 Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Tue, 9 Nov 2021 12:19:51 +0000 Subject: Remove use of ExtendedModSummary --- haddock-api/src/Haddock/Interface.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index e4934711..804367c4 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -69,7 +69,7 @@ import GHC.Types.Name.Occurrence (isTcOcc) import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK) import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet) import GHC.Unit.Module.Graph -import GHC.Unit.Module.ModSummary (emsModSummary, isBootSummary) +import GHC.Unit.Module.ModSummary (isBootSummary) import GHC.Unit.Types (IsBootInterface (..)) import GHC.Utils.Error (withTiming) @@ -212,8 +212,8 @@ createIfaces verbosity modules flags instIfaceMap = do -- i.e. if module A imports B, then B is preferred over A, -- but if module A {-# SOURCE #-} imports B, then we can't say the same. -- - go (AcyclicSCC (ModuleNode ems)) - | NotBoot <- isBootSummary (emsModSummary ems) = [ems] + go (AcyclicSCC (ModuleNode _ ms)) + | NotBoot <- isBootSummary ms = [ms] | otherwise = [] go (AcyclicSCC _) = [] go (CyclicSCC _) = error "haddock: module graph cyclic even with boot files" @@ -222,9 +222,9 @@ createIfaces verbosity modules flags instIfaceMap = do ifaces = [ Map.findWithDefault (error "haddock:iface") - (ms_mod (emsModSummary ems)) + (ms_mod ms) ifaceMap - | ems <- concatMap go $ topSortModuleGraph False modGraph Nothing + | ms <- concatMap go $ topSortModuleGraph False modGraph Nothing ] return (ifaces, moduleSet) -- cgit v1.2.3 From e057bfc880d98fe872e3ee9291d2ee1cd3ceeccd Mon Sep 17 00:00:00 2001 From: John Ericson Date: Mon, 11 Jan 2021 01:06:40 +0000 Subject: Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) --- haddock-api/src/Haddock/Types.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 30f583b0..ba86f429 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -319,7 +319,8 @@ type instance NoGhcTc DocNameI = DocNameI type instance IdP DocNameI = DocName instance CollectPass DocNameI where - collectXXPat _ _ ext = dataConCantHappen ext + collectXXPat _ ext = dataConCantHappen ext + collectXXHsBindsLR ext = dataConCantHappen ext instance NamedThing DocName where getName (Documented name _) = name @@ -828,6 +829,7 @@ type instance XConDeclField DocNameI = NoExtField type instance XXConDeclField DocNameI = DataConCantHappen type instance XXPat DocNameI = DataConCantHappen +type instance XXHsBindsLR DocNameI a = DataConCantHappen type instance XCInjectivityAnn DocNameI = NoExtField -- cgit v1.2.3 From b02188ab1cc46dd82395a22b04f890cf15f3feae Mon Sep 17 00:00:00 2001 From: Vladislav Zavialov Date: Sun, 18 Oct 2020 16:25:35 +0300 Subject: Link to (~) --- haddock-api/src/Haddock/GhcUtils.hs | 1 + haddock-api/src/Haddock/Types.hs | 1 + haddock-library/src/Documentation/Haddock/Parser/Monad.hs | 1 + html-test/ref/FunArgs.html | 4 +++- html-test/ref/TypeOperators.html | 10 ++++++++-- 5 files changed, 14 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 85e6fcf4..3f97236a 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -1,5 +1,6 @@ {-# LANGUAGE BangPatterns, StandaloneDeriving, FlexibleInstances, ViewPatterns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index ba86f429..7d00c5ec 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving, TypeFamilies, RecordWildCards #-} +{-# LANGUAGE TypeOperators #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE PartialTypeSignatures #-} diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs index 7c73a168..2fa79961 100644 --- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs +++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs @@ -2,6 +2,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE TypeSynonymInstances #-} -- | diff --git a/html-test/ref/FunArgs.html b/html-test/ref/FunArgs.html index 2fac6d4e..855f1b89 100644 --- a/html-test/ref/FunArgs.html +++ b/html-test/ref/FunArgs.html @@ -230,7 +230,9 @@ >:: forall a (b :: ()) d. d ~ ' a (b :: ()) d. d ~ '()

    f :: a ~ b => a -> b :: a ~ b => a -> b #

    g :: (a ~ b, b ~ c) => a -> c :: (a ~ b, b ~ c) => a -> c #

    Date: Mon, 19 Apr 2021 19:40:16 +0200 Subject: Add Haddock support for the OPAQUE pragma --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 3929c286..0658d493 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -238,6 +238,7 @@ classify tok = ITrequires -> TkKeyword ITinline_prag {} -> TkPragma + ITopaque_prag {} -> TkPragma ITspec_prag {} -> TkPragma ITspec_inline_prag {} -> TkPragma ITsource_prag {} -> TkPragma @@ -379,6 +380,7 @@ inPragma True _ = True inPragma False tok = case tok of ITinline_prag {} -> True + ITopaque_prag {} -> True ITspec_prag {} -> True ITspec_inline_prag {} -> True ITsource_prag {} -> True -- cgit v1.2.3 From 02803910c1d040222f0bfc5b62411119c443f3a1 Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Wed, 9 Mar 2022 17:23:11 +0000 Subject: Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. --- .../src/Haddock/Backends/Hyperlinker/Parser.hs | 5 +- haddock-api/src/Haddock/GhcUtils.hs | 4 +- haddock-api/src/Haddock/Interface.hs | 4 +- .../src/Haddock/Interface/AttachInstances.hs | 4 +- haddock-api/src/Haddock/Interface/Create.hs | 96 +++++++++++++--------- haddock-api/src/Haddock/Interface/LexParseRn.hs | 12 ++- haddock-api/src/Haddock/Interface/Rename.hs | 7 +- 7 files changed, 79 insertions(+), 53 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 3929c286..a218b118 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -355,10 +355,7 @@ classify tok = ITeof -> TkUnknown ITlineComment {} -> TkComment - ITdocCommentNext {} -> TkComment - ITdocCommentPrev {} -> TkComment - ITdocCommentNamed {} -> TkComment - ITdocSection {} -> TkComment + ITdocComment {} -> TkComment ITdocOptions {} -> TkComment -- The lexer considers top-level pragmas as comments (see `pragState` in diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 3f97236a..9f9120fa 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -96,7 +96,7 @@ ifTrueJust True = Just ifTrueJust False = const Nothing sigName :: LSig GhcRn -> [IdP GhcRn] -sigName (L _ sig) = sigNameNoLoc sig +sigName (L _ sig) = sigNameNoLoc emptyOccEnv sig -- | Was this signature given by the user? isUserLSig :: forall p. UnXRec p => LSig p -> Bool @@ -193,7 +193,7 @@ getMainDeclBinderI (ValD _ d) = case collectHsBindBinders CollNoDictBinders d of [] -> [] (name:_) -> [name] -getMainDeclBinderI (SigD _ d) = sigNameNoLoc d +getMainDeclBinderI (SigD _ d) = sigNameNoLoc emptyOccEnv d getMainDeclBinderI (ForD _ (ForeignImport _ name _ _)) = [unLoc name] getMainDeclBinderI (ForD _ (ForeignExport _ _ _ _)) = [] getMainDeclBinderI _ = [] diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 804367c4..19113107 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -146,7 +146,7 @@ createIfaces verbosity modules flags instIfaceMap = do let installHaddockPlugin :: HscEnv -> HscEnv installHaddockPlugin hsc_env = - let + let old_plugins = hsc_plugins hsc_env new_plugins = old_plugins { staticPlugins = haddockPlugin : staticPlugins old_plugins } hsc_env' = hsc_env { hsc_plugins = new_plugins } @@ -362,7 +362,7 @@ processModule1 verbosity flags ifaces inst_ifaces hsc_env mod_summary tc_gbl_env ] where formatName :: SrcSpan -> HsDecl GhcRn -> String - formatName loc n = p (getMainDeclBinder n) ++ case loc of + formatName loc n = p (getMainDeclBinder emptyOccEnv n) ++ case loc of RealSrcSpan rss _ -> " (" ++ unpackFS (srcSpanFile rss) ++ ":" ++ show (srcSpanStartLine rss) ++ ")" _ -> "" diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index e8a79b2b..dc8afa31 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -136,12 +136,12 @@ attachToExportItem index expInfo getInstDoc getFixity export = , expItemSubDocs = subDocs } = e { expItemFixities = nubByName fst $ expItemFixities e ++ - [ (n',f) | n <- getMainDeclBinder d + [ (n',f) | n <- getMainDeclBinder emptyOccEnv d , n' <- n : (map fst subDocs ++ patsyn_names) , f <- maybeToList (getFixity n') ] } where - patsyn_names = concatMap (getMainDeclBinder . fst) patsyns + patsyn_names = concatMap (getMainDeclBinder emptyOccEnv . fst) patsyns attachFixities e = e -- spanName: attach the location to the name that is the same file as the instance location diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 4d746405..dbd4a9b2 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -35,7 +35,7 @@ import Documentation.Haddock.Doc (metaDocAppend) import Haddock.Convert (PrintRuntimeReps (..), tyThingToLHsDecl) import Haddock.GhcUtils (addClassContext, filterSigNames, lHsQTyVarsToTypes, mkEmptySigType, moduleString, parents, pretty, restrictTo, sigName, unL) -import Haddock.Interface.LexParseRn (processDocString, processDocStringParas, processDocStrings, processModuleHeader) +import Haddock.Interface.LexParseRn import Haddock.Options (Flag (..), modulePackageInfo) import Haddock.Types hiding (liftErrMsg) import Haddock.Utils (replace) @@ -57,7 +57,7 @@ import GHC.Core.Class (ClassMinimalDef, classMinimalDef) import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (bytesFS, unpackFS) import GHC.Driver.Ppr (showSDoc) -import GHC.HsToCore.Docs hiding (mkMaps) +import GHC.HsToCore.Docs hiding (mkMaps, unionArgMaps) import GHC.IORef (readIORef) import GHC.Stack (HasCallStack) import GHC.Tc.Types hiding (IfM) @@ -65,7 +65,7 @@ import GHC.Tc.Utils.Monad (finalSafeMode) import GHC.Types.Avail hiding (avail) import qualified GHC.Types.Avail as Avail import GHC.Types.Basic (PromotionFlag (..)) -import GHC.Types.Name (getOccString, getSrcSpan, isDataConName, isValName, nameIsLocalOrFrom, nameOccName) +import GHC.Types.Name (getOccString, getSrcSpan, isDataConName, isValName, nameIsLocalOrFrom, nameOccName, emptyOccEnv) import GHC.Types.Name.Env (lookupNameEnv) import GHC.Types.Name.Reader (GlobalRdrEnv, greMangledName, lookupGlobalRdrEnv) import GHC.Types.Name.Set (elemNameSet, mkNameSet) @@ -79,6 +79,7 @@ import GHC.Unit.State (PackageName (..), UnitState, lookupModuleInAllUnits) import qualified GHC.Utils.Outputable as O import GHC.Utils.Panic (pprPanic) import GHC.Unit.Module.Warnings +import GHC.Types.Unique.Map newtype IfEnv m = IfEnv { @@ -255,7 +256,7 @@ createInterface1 flags unit_state mod_sum tc_gbl_env ifaces inst_ifaces = do -- Process the top-level module header documentation. (!info, header_doc) <- liftErrMsg $ processModuleHeader dflags pkg_name - tcg_rdr_env safety (thMbDocStr <|> (unLoc <$> tcg_doc_hdr)) + tcg_rdr_env safety (fmap hsDocString thMbDocStr <|> (hsDocString . unLoc <$> tcg_doc_hdr)) -- Warnings on declarations in this module decl_warnings <- liftErrMsg (mkWarningMap dflags tcg_warns tcg_rdr_env exported_names) @@ -405,7 +406,7 @@ lookupModuleDyn state pkg_qual mdlName = case pkg_qual of -- Warnings ------------------------------------------------------------------------------- -mkWarningMap :: DynFlags -> Warnings -> GlobalRdrEnv -> [Name] -> ErrMsgM WarningMap +mkWarningMap :: DynFlags -> Warnings a -> GlobalRdrEnv -> [Name] -> ErrMsgM WarningMap mkWarningMap dflags warnings gre exps = case warnings of NoWarnings -> pure M.empty WarnAll _ -> pure M.empty @@ -416,18 +417,18 @@ mkWarningMap dflags warnings gre exps = case warnings of , let n = greMangledName elt, n `elem` exps ] in M.fromList <$> traverse (bitraverse pure (parseWarning dflags gre)) ws' -moduleWarning :: DynFlags -> GlobalRdrEnv -> Warnings -> ErrMsgM (Maybe (Doc Name)) +moduleWarning :: DynFlags -> GlobalRdrEnv -> Warnings a -> ErrMsgM (Maybe (Doc Name)) moduleWarning _ _ NoWarnings = pure Nothing moduleWarning _ _ (WarnSome _) = pure Nothing moduleWarning dflags gre (WarnAll w) = Just <$> parseWarning dflags gre w -parseWarning :: DynFlags -> GlobalRdrEnv -> WarningTxt -> ErrMsgM (Doc Name) +parseWarning :: DynFlags -> GlobalRdrEnv -> WarningTxt a -> ErrMsgM (Doc Name) parseWarning dflags gre w = case w of - DeprecatedTxt _ msg -> format "Deprecated: " (foldMap (bytesFS . sl_fs . unLoc) msg) - WarningTxt _ msg -> format "Warning: " (foldMap (bytesFS . sl_fs . unLoc) msg) + DeprecatedTxt _ msg -> format "Deprecated: " (foldMap (unpackFS . sl_fs . hsDocString . unLoc) msg) + WarningTxt _ msg -> format "Warning: " (foldMap (unpackFS . sl_fs . hsDocString . unLoc) msg) where format x bs = DocWarning . DocParagraph . DocAppend (DocString x) - <$> processDocString dflags gre (mkHsDocStringUtf8ByteString bs) + <$> processDocStringFromString dflags gre bs ------------------------------------------------------------------------------- @@ -479,7 +480,7 @@ mkMaps :: DynFlags -> Maybe Package -- this package -> GlobalRdrEnv -> [Name] - -> [(LHsDecl GhcRn, [HsDocString])] + -> [(LHsDecl GhcRn, [HsDoc GhcRn])] -> ExtractedTHDocs -- ^ Template Haskell putDoc docs -> ErrMsgM Maps mkMaps dflags pkgName gre instances decls thDocs = do @@ -512,36 +513,40 @@ mkMaps dflags pkgName gre instances decls thDocs = do thMappings = do let ExtractedTHDocs _ - (DeclDocMap declDocs) - (ArgDocMap argDocs) - (DeclDocMap instDocs) = thDocs - ds2mdoc :: HsDocString -> ErrMsgM (MDoc Name) - ds2mdoc = processDocStringParas dflags pkgName gre - - declDocs' <- mapM ds2mdoc declDocs - argDocs' <- mapM (mapM ds2mdoc) argDocs - instDocs' <- mapM ds2mdoc instDocs + declDocs + argDocs + instDocs = thDocs + ds2mdoc :: (HsDoc GhcRn) -> ErrMsgM (MDoc Name) + ds2mdoc = processDocStringParas dflags pkgName gre . hsDocString + + let cvt = M.fromList . nonDetEltsUniqMap + + declDocs' <- mapM ds2mdoc (cvt declDocs) + argDocs' <- mapM (mapM ds2mdoc) (cvt argDocs) + instDocs' <- mapM ds2mdoc (cvt instDocs) return (declDocs' <> instDocs', argDocs') - mappings :: (LHsDecl GhcRn, [HsDocString]) + mappings :: (LHsDecl GhcRn, [HsDoc GhcRn]) -> ErrMsgM ( [(Name, MDoc Name)] , [(Name, IntMap (MDoc Name))] , [(Name, [LHsDecl GhcRn])] ) - mappings (ldecl@(L (SrcSpanAnn _ (RealSrcSpan l _)) decl), docStrs) = do - let declDoc :: [HsDocString] -> IntMap HsDocString + mappings (ldecl@(L (SrcSpanAnn _ (RealSrcSpan l _)) decl), hs_docStrs) = do + let docStrs = map hsDocString hs_docStrs + declDoc :: [HsDocString] -> IntMap HsDocString -> ErrMsgM (Maybe (MDoc Name), IntMap (MDoc Name)) declDoc strs m = do doc' <- processDocStrings dflags pkgName gre strs m' <- traverse (processDocStringParas dflags pkgName gre) m pure (doc', m') - (doc, args) <- declDoc docStrs (declTypeDocs decl) + (doc, args) <- declDoc docStrs (fmap hsDocString (declTypeDocs decl)) let subs :: [(Name, [HsDocString], IntMap HsDocString)] - subs = subordinates instanceMap decl + subs = map (\(n, ds, im) -> (n, map hsDocString ds, fmap hsDocString im)) + $ subordinates emptyOccEnv instanceMap decl (subDocs, subArgs) <- unzip <$> traverse (\(_, strs, m) -> declDoc strs m) subs @@ -572,7 +577,23 @@ mkMaps dflags pkgName gre instances decls thDocs = do TyFamInstD _ (TyFamInstDecl _ d') -> getLocA (feqn_tycon d') _ -> getInstLoc d names l (DerivD {}) = maybeToList (M.lookup l instanceMap) -- See note [2]. - names _ decl = getMainDeclBinder decl + names _ decl = getMainDeclBinder emptyOccEnv decl + +-- | Unions together two 'ArgDocMaps' (or ArgMaps in haddock-api), such that two +-- maps with values for the same key merge the inner map as well. +-- Left biased so @unionArgMaps a b@ prefers @a@ over @b@. + +unionArgMaps :: forall b . Map Name (IntMap b) + -> Map Name (IntMap b) + -> Map Name (IntMap b) +unionArgMaps a b = M.foldrWithKey go b a + where + go :: Name -> IntMap b + -> Map Name (IntMap b) -> Map Name (IntMap b) + go n newArgMap acc + | Just oldArgMap <- M.lookup n acc = + M.insert n (newArgMap `IM.union` oldArgMap) acc + | otherwise = M.insert n newArgMap acc -- Note [2]: ------------ @@ -634,11 +655,11 @@ mkExportItems Just exports -> liftM concat $ mapM lookupExport exports where lookupExport (IEGroup _ lev docStr, _) = liftErrMsg $ do - doc <- processDocString dflags gre docStr + doc <- processDocString dflags gre (hsDocString . unLoc $ docStr) return [ExportGroup lev "" doc] lookupExport (IEDoc _ docStr, _) = liftErrMsg $ do - doc <- processDocStringParas dflags pkgName gre docStr + doc <- processDocStringParas dflags pkgName gre (hsDocString . unLoc $ docStr) return [ExportDoc doc] lookupExport (IEDocNamed _ str, _) = liftErrMsg $ @@ -706,7 +727,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames export <- hiValExportItem dflags t l doc (l `elem` splices) $ M.lookup t fixMap return [export] (ds, docs_) | decl : _ <- filter (not . isValD . unLoc) ds -> - let declNames = getMainDeclBinder (unL decl) + let declNames = getMainDeclBinder emptyOccEnv (unL decl) in case () of _ -- We should not show a subordinate by itself if any of its @@ -785,7 +806,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames let patSynNames = - concatMap (getMainDeclBinder . fst) bundledPatSyns + concatMap (getMainDeclBinder emptyOccEnv . fst) bundledPatSyns fixities = [ (n, f) @@ -1007,17 +1028,17 @@ fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre exportedNam (concat . concat) `fmap` (for decls $ \decl -> do case decl of (L _ (DocD _ (DocGroup lev docStr))) -> do - doc <- liftErrMsg (processDocString dflags gre docStr) + doc <- liftErrMsg (processDocString dflags gre (hsDocString . unLoc $ docStr)) return [[ExportGroup lev "" doc]] (L _ (DocD _ (DocCommentNamed _ docStr))) -> do - doc <- liftErrMsg (processDocStringParas dflags pkgName gre docStr) + doc <- liftErrMsg (processDocStringParas dflags pkgName gre (hsDocString . unLoc $ docStr)) return [[ExportDoc doc]] (L _ (ValD _ valDecl)) | name:_ <- collectHsBindBinders CollNoDictBinders valDecl , Just (L _ SigD{}:_) <- filter isSigD <$> M.lookup name declMap -> return [] _ -> - for (getMainDeclBinder (unLoc decl)) $ \nm -> do + for (getMainDeclBinder emptyOccEnv (unLoc decl)) $ \nm -> do case lookupNameEnv availEnv nm of Just avail -> availExportItem is_sig modMap thisMod @@ -1042,7 +1063,7 @@ extractDecl -> LHsDecl GhcRn -- ^ parent declaration -> Either ErrMsg (LHsDecl GhcRn) extractDecl declMap name decl - | name `elem` getMainDeclBinder (unLoc decl) = pure decl + | name `elem` getMainDeclBinder emptyOccEnv (unLoc decl) = pure decl | otherwise = case unLoc decl of TyClD _ d@ClassDecl { tcdLName = L _ clsNm @@ -1197,10 +1218,10 @@ mkVisibleNames (_, _, _, instMap) exports opts where exportName e@ExportDecl {} = name ++ subs ++ patsyns where subs = map fst (expItemSubDocs e) - patsyns = concatMap (getMainDeclBinder . fst) (expItemPats e) + patsyns = concatMap (getMainDeclBinder emptyOccEnv . fst) (expItemPats e) name = case unLoc $ expItemDecl e of InstD _ d -> maybeToList $ SrcLoc.lookupSrcSpan (getInstLoc d) instMap - decl -> getMainDeclBinder decl + decl -> getMainDeclBinder emptyOccEnv decl exportName ExportNoDecl {} = [] -- we don't count these as visible, since -- we don't want links to go to them. exportName _ = [] @@ -1217,6 +1238,7 @@ findNamedDoc name = search tell ["Cannot find documentation for: $" ++ name] return Nothing search (DocD _ (DocCommentNamed name' doc) : rest) - | name == name' = return (Just doc) + | name == name' = return (Just (hsDocString . unLoc $ doc)) + | otherwise = search rest search (_other_decl : rest) = search rest diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index a827cf66..f3b57792 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -15,6 +15,7 @@ ----------------------------------------------------------------------------- module Haddock.Interface.LexParseRn ( processDocString + , processDocStringFromString , processDocStringParas , processDocStrings , processModuleHeader @@ -38,6 +39,7 @@ import GHC.Parser.PostProcess import GHC.Driver.Ppr ( showPpr, showSDoc ) import GHC.Types.Name.Reader import GHC.Data.EnumSet as EnumSet +import GHC.Utils.Trace processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString] -> ErrMsgM (Maybe (MDoc Name)) @@ -52,11 +54,15 @@ processDocStrings dflags pkg gre strs = do processDocStringParas :: DynFlags -> Maybe Package -> GlobalRdrEnv -> HsDocString -> ErrMsgM (MDoc Name) processDocStringParas dflags pkg gre hds = - overDocF (rename dflags gre) $ parseParas dflags pkg (unpackHDS hds) + overDocF (rename dflags gre) $ parseParas dflags pkg (renderHsDocString hds) processDocString :: DynFlags -> GlobalRdrEnv -> HsDocString -> ErrMsgM (Doc Name) processDocString dflags gre hds = - rename dflags gre $ parseString dflags (unpackHDS hds) + processDocStringFromString dflags gre (renderHsDocString hds) + +processDocStringFromString :: DynFlags -> GlobalRdrEnv -> String -> ErrMsgM (Doc Name) +processDocStringFromString dflags gre hds = + rename dflags gre $ parseString dflags hds processModuleHeader :: DynFlags -> Maybe Package -> GlobalRdrEnv -> SafeHaskellMode -> Maybe HsDocString -> ErrMsgM (HaddockModInfo Name, Maybe (MDoc Name)) @@ -65,7 +71,7 @@ processModuleHeader dflags pkgName gre safety mayStr = do case mayStr of Nothing -> return failure Just hds -> do - let str = unpackHDS hds + let str = renderHsDocString hds (hmi, doc) = parseModuleHeader dflags pkgName str !descr <- case hmi_description hmi of Just hmi_descr -> Just <$> rename dflags gre hmi_descr diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 98c39859..f2b3a9fa 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -191,8 +191,8 @@ renameDocumentation (Documentation mDoc mWarning) = Documentation <$> mapM renameDoc mDoc <*> mapM renameDoc mWarning -renameLDocHsSyn :: LHsDocString -> RnM LHsDocString -renameLDocHsSyn = return +renameLDocHsSyn :: Located (WithHsDocIdentifiers HsDocString a) -> RnM (Located (WithHsDocIdentifiers HsDocString b)) +renameLDocHsSyn (L l doc) = return (L l (WithHsDocIdentifiers (hsDocString doc) [])) renameDoc :: Traversable t => t (Wrap Name) -> RnM (t (Wrap DocName)) @@ -317,6 +317,7 @@ renameType t = case t of HsSpliceTy _ s -> renameHsSpliceTy s HsWildCardTy _ -> pure (HsWildCardTy noAnn) + renameSigType :: HsSigType GhcRn -> RnM (HsSigType DocNameI) renameSigType (HsSig { sig_bndrs = bndrs, sig_body = body }) = do bndrs' <- renameOuterTyVarBndrs bndrs @@ -511,7 +512,7 @@ renameCon decl@(ConDeclH98 { con_name = lname, con_ex_tvs = ltyvars ltyvars' <- mapM renameLTyVarBndr ltyvars lcontext' <- traverse renameLContext lcontext details' <- renameH98Details details - mbldoc' <- mapM renameLDocHsSyn mbldoc + mbldoc' <- mapM (renameLDocHsSyn) mbldoc return (decl { con_ext = noExtField, con_name = lname', con_ex_tvs = ltyvars' , con_mb_cxt = lcontext' , con_forall = forall_ -- Remove when #18311 is fixed -- cgit v1.2.3 From d2779a3e659d4e9f7044c346a566e5fe4edbdb9b Mon Sep 17 00:00:00 2001 From: Matthew Pickering Date: Tue, 22 Mar 2022 21:17:50 +0000 Subject: Update test output --- hypsrc-test/ref/src/Quasiquoter.html | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/hypsrc-test/ref/src/Quasiquoter.html b/hypsrc-test/ref/src/Quasiquoter.html index 53dc3474..76faac5a 100644 --- a/hypsrc-test/ref/src/Quasiquoter.html +++ b/hypsrc-test/ref/src/Quasiquoter.html @@ -80,8 +80,10 @@ -- | Quoter for constructing multiline string literals-- | Quoter for constructing multiline string literals Date: Tue, 29 Mar 2022 16:36:45 +0200 Subject: Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. --- haddock-api/src/Haddock/Backends/Hoogle.hs | 2 +- haddock-api/src/Haddock/Backends/LaTeX.hs | 10 +++++++--- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 16 ++++++++-------- haddock-api/src/Haddock/Convert.hs | 8 +++++--- haddock-api/src/Haddock/GhcUtils.hs | 6 +++--- haddock-api/src/Haddock/Interface/Rename.hs | 4 ++-- haddock-api/src/Haddock/Interface/Specialize.hs | 9 +++++---- 7 files changed, 31 insertions(+), 24 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 29c64a2d..221580cc 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -87,7 +87,7 @@ dropHsDocTy = drop_sig_ty drop_ty (HsFunTy x w a b) = HsFunTy x w (drop_lty a) (drop_lty b) drop_ty (HsListTy x a) = HsListTy x (drop_lty a) drop_ty (HsTupleTy x a b) = HsTupleTy x a (map drop_lty b) - drop_ty (HsOpTy x a b c) = HsOpTy x (drop_lty a) b (drop_lty c) + drop_ty (HsOpTy x p a b c) = HsOpTy x p (drop_lty a) b (drop_lty c) drop_ty (HsParTy x a) = HsParTy x (drop_lty a) drop_ty (HsKindSig x a b) = HsKindSig x (drop_lty a) b drop_ty (HsDocTy _ a _) = drop_ty $ unL a diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index eb524ec7..349c6e8e 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -24,7 +24,7 @@ import Haddock.GhcUtils import GHC.Utils.Ppr hiding (Doc, quote) import qualified GHC.Utils.Ppr as Pretty -import GHC.Types.Basic ( PromotionFlag(..) ) +import GHC.Types.Basic ( PromotionFlag(..), isPromoted ) import GHC hiding (fromMaybeContext ) import GHC.Types.Name.Occurrence import GHC.Types.Name ( nameOccName ) @@ -1133,9 +1133,13 @@ ppr_mono_ty (HsAppTy _ fun_ty arg_ty) unicode ppr_mono_ty (HsAppKindTy _ fun_ty arg_ki) unicode = hsep [ppr_mono_lty fun_ty unicode, atSign unicode <> ppr_mono_lty arg_ki unicode] -ppr_mono_ty (HsOpTy _ ty1 op ty2) unicode - = ppr_mono_lty ty1 unicode <+> ppr_op <+> ppr_mono_lty ty2 unicode +ppr_mono_ty (HsOpTy _ prom ty1 op ty2) unicode + = ppr_mono_lty ty1 unicode <+> ppr_op_prom <+> ppr_mono_lty ty2 unicode where + ppr_op_prom | isPromoted prom + = char '\'' <> ppr_op + | otherwise + = ppr_op ppr_op | isSymOcc (getOccName op) = ppLDocName op | otherwise = char '`' <> ppLDocName op <> char '`' diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 336f23ac..a54bb0aa 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -1281,15 +1281,15 @@ ppr_mono_ty (HsAppKindTy _ fun_ty arg_ki) unicode qual _ = hsep [ppr_mono_lty fun_ty unicode qual HideEmptyContexts , atSign unicode <> ppr_mono_lty arg_ki unicode qual HideEmptyContexts] -ppr_mono_ty (HsOpTy _ ty1 op ty2) unicode qual _ - = ppr_mono_lty ty1 unicode qual HideEmptyContexts <+> ppr_op <+> ppr_mono_lty ty2 unicode qual HideEmptyContexts +ppr_mono_ty (HsOpTy _ prom ty1 op ty2) unicode qual _ + = ppr_mono_lty ty1 unicode qual HideEmptyContexts <+> ppr_op_prom <+> ppr_mono_lty ty2 unicode qual HideEmptyContexts where - -- `(:)` is valid in type signature only as constructor to promoted list - -- and needs to be quoted in code so we explicitly quote it here too. - ppr_op - | (getOccString . getName . unL) op == ":" = promoQuote ppr_op' - | otherwise = ppr_op' - ppr_op' = ppLDocName qual Infix op + ppr_op_prom + | isPromoted prom + = promoQuote ppr_op + | otherwise + = ppr_op + ppr_op = ppLDocName qual Infix op ppr_mono_ty (HsParTy _ ty) unicode qual emptyCtxts = parens (ppr_mono_lty ty unicode qual emptyCtxts) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index 29e0957b..fd5300d2 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -606,7 +606,7 @@ synifyType _ vs (TyConApp tc tys) tTy | L _ (HsExplicitListTy _ IsPromoted tTy') <- stripKindSig tTy -> noLocA $ HsExplicitListTy noExtField IsPromoted (hTy : tTy') | otherwise - -> noLocA $ HsOpTy noExtField hTy (noLocA $ getName tc) tTy + -> noLocA $ HsOpTy noAnn IsPromoted hTy (noLocA $ getName tc) tTy -- ditto for implicit parameter tycons | tc `hasKey` ipClassKey , [name, ty] <- tys @@ -615,14 +615,16 @@ synifyType _ vs (TyConApp tc tys) -- and equalities | tc `hasKey` eqTyConKey , [ty1, ty2] <- tys - = noLocA $ HsOpTy noExtField + = noLocA $ HsOpTy noAnn + NotPromoted (synifyType WithinType vs ty1) (noLocA eqTyConName) (synifyType WithinType vs ty2) -- and infix type operators | isSymOcc (nameOccName (getName tc)) , ty1:ty2:tys_rest <- vis_tys - = mk_app_tys (HsOpTy noExtField + = mk_app_tys (HsOpTy noAnn + prom (synifyType WithinType vs ty1) (noLocA $ getName tc) (synifyType WithinType vs ty2)) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 9f9120fa..7c1dc73b 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -229,7 +229,7 @@ addClassContext cls tvs0 (L pos (ClassOpSig _ _ lname ltype)) = L loc (HsQualTy { hst_xqual = noExtField , hst_ctxt = add_ctxt (noLocA []), hst_body = L loc ty }) - extra_pred = nlHsTyConApp Prefix cls (lHsQTyVarsToTypes tvs0) + extra_pred = nlHsTyConApp NotPromoted Prefix cls (lHsQTyVarsToTypes tvs0) add_ctxt (L loc preds) = L loc (extra_pred : preds) @@ -365,8 +365,8 @@ reparenTypePrec = go = paren p PREC_CON $ HsAppTy x (goL PREC_FUN fun_ty) (goL PREC_CON arg_ty) go p (HsAppKindTy x fun_ty arg_ki) = paren p PREC_CON $ HsAppKindTy x (goL PREC_FUN fun_ty) (goL PREC_CON arg_ki) - go p (HsOpTy x ty1 op ty2) - = paren p PREC_FUN $ HsOpTy x (goL PREC_OP ty1) op (goL PREC_OP ty2) + go p (HsOpTy x prom ty1 op ty2) + = paren p PREC_FUN $ HsOpTy x prom (goL PREC_OP ty1) op (goL PREC_OP ty2) go p (HsParTy _ t) = unXRec @a $ goL p t -- pretend the paren doesn't exist - it will be added back if needed go _ t@HsTyVar{} = t go _ t@HsStarTy{} = t diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index f2b3a9fa..6057bf75 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -290,11 +290,11 @@ renameType t = case t of HsTupleTy _ b ts -> return . HsTupleTy noAnn b =<< mapM renameLType ts HsSumTy _ ts -> HsSumTy noAnn <$> mapM renameLType ts - HsOpTy _ a (L loc op) b -> do + HsOpTy _ prom a (L loc op) b -> do op' <- rename op a' <- renameLType a b' <- renameLType b - return (HsOpTy noAnn a' (L loc op') b') + return (HsOpTy noAnn prom a' (L loc op') b') HsParTy _ ty -> return . (HsParTy noAnn) =<< renameLType ty diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index 399e5d0d..d1164858 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -16,6 +16,7 @@ import Haddock.Syb import Haddock.Types import GHC +import GHC.Types.Basic ( PromotionFlag(..) ) import GHC.Types.Name import GHC.Data.FastString import GHC.Builtin.Types ( listTyConName, unrestrictedFunTyConName ) @@ -132,8 +133,8 @@ sugarTuples typ = sugarOperators :: HsType GhcRn -> HsType GhcRn -sugarOperators (HsAppTy _ (L _ (HsAppTy _ (L _ (HsTyVar _ _ (L l name))) la)) lb) - | isSymOcc $ getOccName name' = mkHsOpTy la (L l name) lb +sugarOperators (HsAppTy _ (L _ (HsAppTy _ (L _ (HsTyVar _ prom (L l name))) la)) lb) + | isSymOcc $ getOccName name' = mkHsOpTy prom la (L l name) lb | unrestrictedFunTyConName == name' = HsFunTy noAnn (HsUnrestrictedArrow noHsUniTok) la lb where name' = getName name @@ -293,8 +294,8 @@ renameType (HsFunTy x w la lr) = HsFunTy x <$> renameHsArrow w <*> renameLType l renameType (HsListTy x lt) = HsListTy x <$> renameLType lt renameType (HsTupleTy x srt lt) = HsTupleTy x srt <$> mapM renameLType lt renameType (HsSumTy x lt) = HsSumTy x <$> mapM renameLType lt -renameType (HsOpTy x la lop lb) = - HsOpTy x <$> renameLType la <*> locatedN renameName lop <*> renameLType lb +renameType (HsOpTy x prom la lop lb) = + HsOpTy x prom <$> renameLType la <*> locatedN renameName lop <*> renameLType lb renameType (HsParTy x lt) = HsParTy x <$> renameLType lt renameType (HsIParamTy x ip lt) = HsIParamTy x ip <$> renameLType lt renameType (HsKindSig x lt lk) = HsKindSig x <$> renameLType lt <*> pure lk -- cgit v1.2.3 From fb0e9bac0a5297f995b151f25aa1ce3e622e12ea Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jakob=20Br=C3=BCnker?= Date: Sun, 27 Mar 2022 12:03:12 +0000 Subject: Add support for \cases See merge request ghc/ghc!7873 --- haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs index 76ae5be3..9f28d72a 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs @@ -269,6 +269,7 @@ classify tok = ITequal -> TkGlyph ITlam -> TkGlyph ITlcase -> TkGlyph + ITlcases -> TkGlyph ITvbar -> TkGlyph ITlarrow {} -> TkGlyph ITrarrow {} -> TkGlyph -- cgit v1.2.3 From d504cd50d8b660c207573864890392f02a48ca54 Mon Sep 17 00:00:00 2001 From: Vladislav Zavialov Date: Mon, 28 Mar 2022 15:00:51 +0300 Subject: Rename [] to List --- html-test/ref/Instances.html | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html index e99f82e4..109e866c 100644 --- a/html-test/ref/Instances.html +++ b/html-test/ref/Instances.html @@ -262,7 +262,9 @@ > Foo [] List # Bar [] (a, a) List (a, a) # Date: Fri, 1 Apr 2022 14:32:36 +0300 Subject: HsToken ConDeclGADT con_dcolon --- haddock-api/src/Haddock/Convert.hs | 1 + haddock-api/src/Haddock/Interface/Rename.hs | 4 +++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index fd5300d2..ceefedf3 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -411,6 +411,7 @@ synifyDataCon use_gadt_syntax dc = return $ noLocA $ ConDeclGADT { con_g_ext = noAnn , con_names = [name] + , con_dcolon = noHsUniTok , con_bndrs = noLocA outer_bndrs , con_mb_cxt = ctx , con_g_args = hat diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 6057bf75..cbc7e58f 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -519,6 +519,7 @@ renameCon decl@(ConDeclH98 { con_name = lname, con_ex_tvs = ltyvars , con_args = details', con_doc = mbldoc' }) renameCon ConDeclGADT { con_names = lnames, con_bndrs = bndrs + , con_dcolon = dcol , con_mb_cxt = lcontext, con_g_args = details , con_res_ty = res_ty , con_doc = mbldoc } = do @@ -529,7 +530,8 @@ renameCon ConDeclGADT { con_names = lnames, con_bndrs = bndrs res_ty' <- renameLType res_ty mbldoc' <- mapM renameLDocHsSyn mbldoc return (ConDeclGADT - { con_g_ext = noExtField, con_names = lnames', con_bndrs = bndrs' + { con_g_ext = noExtField, con_names = lnames' + , con_dcolon = dcol, con_bndrs = bndrs' , con_mb_cxt = lcontext', con_g_args = details' , con_res_ty = res_ty', con_doc = mbldoc' }) -- cgit v1.2.3 From 7a10420bd523dfe1eebdb337492917f7bd4cb433 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Sat, 23 Apr 2022 22:54:37 -0400 Subject: Update for GHC 9.4 --- haddock-api/src/Haddock/InterfaceFile.hs | 4 ++-- haddock.cabal | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 9c4308a6..db5181c6 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -85,8 +85,8 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if MIN_VERSION_ghc(9,3,0) && !MIN_VERSION_ghc(9,4,0) -binaryInterfaceVersion = 39 +#if MIN_VERSION_ghc(9,4,0) && !MIN_VERSION_ghc(9,5,0) +binaryInterfaceVersion = 40 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] diff --git a/haddock.cabal b/haddock.cabal index dfb4e9a9..5c09f80d 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -81,7 +81,7 @@ executable haddock xhtml >= 3000.2 && < 3000.3, ghc-boot, ghc-boot-th, - ghc == 9.3.*, + ghc == 9.4.*, bytestring, parsec, text, -- cgit v1.2.3 From 7921211350a572d5365e7feb5fa4cc04666318e8 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Mon, 25 Apr 2022 17:00:25 -0400 Subject: Bump ghc version to 9.5 --- haddock-api/src/Haddock/InterfaceFile.hs | 4 ++-- haddock.cabal | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 9c4308a6..aabb904a 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -85,8 +85,8 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if MIN_VERSION_ghc(9,3,0) && !MIN_VERSION_ghc(9,4,0) -binaryInterfaceVersion = 39 +#if MIN_VERSION_ghc(9,5,0) && !MIN_VERSION_ghc(9,6,0) +binaryInterfaceVersion = 41 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] diff --git a/haddock.cabal b/haddock.cabal index 0686289e..672420bd 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -81,7 +81,7 @@ executable haddock xhtml >= 3000.2 && < 3000.3, ghc-boot, ghc-boot-th, - ghc == 9.3.*, + ghc == 9.5.*, bytestring, parsec, text, -- cgit v1.2.3 From 2627a86cb2dd3256c93adf0df8a7d3366a303b02 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Thu, 28 Apr 2022 16:19:04 -0400 Subject: Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. --- haddock-api/src/Haddock/GhcUtils.hs | 2 +- haddock-api/src/Haddock/Interface.hs | 14 ++++++-------- haddock-api/src/Haddock/Types.hs | 24 ++++++++++++------------ html-test/ref/Identifiers.html | 10 +++++----- 4 files changed, 24 insertions(+), 26 deletions(-) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 85e6fcf4..599404a0 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -114,7 +114,7 @@ pretty = showPpr -- instantiated at DocNameI instead of (GhcPass _). -- | Like 'hsTyVarName' from GHC API, but not instantiated at (GhcPass _) -hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ DataConCantHappen, UnXRec n) +hsTyVarBndrName :: forall flag n. (XXTyVarBndr n ~ NoExtCon, UnXRec n) => HsTyVarBndr flag n -> IdP n hsTyVarBndrName (UserTyVar _ _ name) = unXRec @n name hsTyVarBndrName (KindedTyVar _ _ name _) = unXRec @n name diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index e4934711..ba7d9d30 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -56,11 +56,11 @@ import qualified Data.Set as Set import GHC hiding (verbosity) import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed -import GHC.Driver.Env +import GHC.Driver.Env (hscUpdateFlags, hsc_home_unit, hsc_logger, hsc_static_plugins, hsc_units) import GHC.Driver.Monad (modifySession, withTimingM) import GHC.Driver.Session hiding (verbosity) import GHC.HsToCore.Docs (getMainDeclBinder) -import GHC.Plugins +import GHC.Plugins (Outputable, Plugin (..), PluginWithArgs (..), StaticPlugin (..), defaultPlugin, keepRenamedSource) import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) @@ -145,12 +145,10 @@ createIfaces verbosity modules flags instIfaceMap = do let installHaddockPlugin :: HscEnv -> HscEnv - installHaddockPlugin hsc_env = - let - old_plugins = hsc_plugins hsc_env - new_plugins = old_plugins { staticPlugins = haddockPlugin : staticPlugins old_plugins } - hsc_env' = hsc_env { hsc_plugins = new_plugins } - in hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) hsc_env' + installHaddockPlugin hsc_env = hscUpdateFlags (flip gopt_set Opt_PluginTrustworthy) $ hsc_env + { hsc_static_plugins = + haddockPlugin : hsc_static_plugins hsc_env + } -- Note that we would rather use withTempSession but as long as we -- have the separate attachInstances step we need to keep the session diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index 30f583b0..05375185 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -319,7 +319,7 @@ type instance NoGhcTc DocNameI = DocNameI type instance IdP DocNameI = DocName instance CollectPass DocNameI where - collectXXPat _ _ ext = dataConCantHappen ext + collectXXPat _ _ ext = noExtCon ext instance NamedThing DocName where getName (Documented name _) = name @@ -760,11 +760,11 @@ type instance XXType DocNameI = HsCoreTy type instance XHsForAllVis DocNameI = NoExtField type instance XHsForAllInvis DocNameI = NoExtField -type instance XXHsForAllTelescope DocNameI = DataConCantHappen +type instance XXHsForAllTelescope DocNameI = NoExtCon type instance XUserTyVar DocNameI = NoExtField type instance XKindedTyVar DocNameI = NoExtField -type instance XXTyVarBndr DocNameI = DataConCantHappen +type instance XXTyVarBndr DocNameI = NoExtCon type instance XCFieldOcc DocNameI = DocName type instance XXFieldOcc DocNameI = NoExtField @@ -780,7 +780,7 @@ type instance XForeignExport DocNameI = NoExtField type instance XForeignImport DocNameI = NoExtField type instance XConDeclGADT DocNameI = NoExtField type instance XConDeclH98 DocNameI = NoExtField -type instance XXConDecl DocNameI = DataConCantHappen +type instance XXConDecl DocNameI = NoExtCon type instance XDerivD DocNameI = NoExtField type instance XInstD DocNameI = NoExtField @@ -791,10 +791,10 @@ type instance XTyClD DocNameI = NoExtField type instance XNoSig DocNameI = NoExtField type instance XCKindSig DocNameI = NoExtField type instance XTyVarSig DocNameI = NoExtField -type instance XXFamilyResultSig DocNameI = DataConCantHappen +type instance XXFamilyResultSig DocNameI = NoExtCon type instance XCFamEqn DocNameI _ = NoExtField -type instance XXFamEqn DocNameI _ = DataConCantHappen +type instance XXFamEqn DocNameI _ = NoExtCon type instance XCClsInstDecl DocNameI = NoExtField type instance XCDerivDecl DocNameI = NoExtField @@ -811,23 +811,23 @@ type instance XClassDecl DocNameI = NoExtField type instance XDataDecl DocNameI = NoExtField type instance XSynDecl DocNameI = NoExtField type instance XFamDecl DocNameI = NoExtField -type instance XXFamilyDecl DocNameI = DataConCantHappen -type instance XXTyClDecl DocNameI = DataConCantHappen +type instance XXFamilyDecl DocNameI = NoExtCon +type instance XXTyClDecl DocNameI = NoExtCon type instance XHsWC DocNameI _ = NoExtField type instance XHsOuterExplicit DocNameI _ = NoExtField type instance XHsOuterImplicit DocNameI = NoExtField -type instance XXHsOuterTyVarBndrs DocNameI = DataConCantHappen +type instance XXHsOuterTyVarBndrs DocNameI = NoExtCon type instance XHsSig DocNameI = NoExtField -type instance XXHsSigType DocNameI = DataConCantHappen +type instance XXHsSigType DocNameI = NoExtCon type instance XHsQTvs DocNameI = NoExtField type instance XConDeclField DocNameI = NoExtField -type instance XXConDeclField DocNameI = DataConCantHappen +type instance XXConDeclField DocNameI = NoExtCon -type instance XXPat DocNameI = DataConCantHappen +type instance XXPat DocNameI = NoExtCon type instance XCInjectivityAnn DocNameI = NoExtField diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html index 76487140..b177266d 100644 --- a/html-test/ref/Identifiers.html +++ b/html-test/ref/Identifiers.html @@ -147,7 +147,7 @@ >, elemFoldable
  • ++, elemFoldable, elemUnqualified: 1 `elem``Foldable` [-3..3]
  • Qualified: 1 `elem` [-3..3]
  • Namespaced: `elem``Foldable`, `elem` Date: Fri, 29 Apr 2022 11:46:06 -0400 Subject: Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. --- haddock-api/src/Haddock/Convert.hs | 1 - haddock-api/src/Haddock/Interface/Rename.hs | 4 +--- 2 files changed, 1 insertion(+), 4 deletions(-) diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs index ceefedf3..fd5300d2 100644 --- a/haddock-api/src/Haddock/Convert.hs +++ b/haddock-api/src/Haddock/Convert.hs @@ -411,7 +411,6 @@ synifyDataCon use_gadt_syntax dc = return $ noLocA $ ConDeclGADT { con_g_ext = noAnn , con_names = [name] - , con_dcolon = noHsUniTok , con_bndrs = noLocA outer_bndrs , con_mb_cxt = ctx , con_g_args = hat diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index cbc7e58f..6057bf75 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -519,7 +519,6 @@ renameCon decl@(ConDeclH98 { con_name = lname, con_ex_tvs = ltyvars , con_args = details', con_doc = mbldoc' }) renameCon ConDeclGADT { con_names = lnames, con_bndrs = bndrs - , con_dcolon = dcol , con_mb_cxt = lcontext, con_g_args = details , con_res_ty = res_ty , con_doc = mbldoc } = do @@ -530,8 +529,7 @@ renameCon ConDeclGADT { con_names = lnames, con_bndrs = bndrs res_ty' <- renameLType res_ty mbldoc' <- mapM renameLDocHsSyn mbldoc return (ConDeclGADT - { con_g_ext = noExtField, con_names = lnames' - , con_dcolon = dcol, con_bndrs = bndrs' + { con_g_ext = noExtField, con_names = lnames', con_bndrs = bndrs' , con_mb_cxt = lcontext', con_g_args = details' , con_res_ty = res_ty', con_doc = mbldoc' }) -- cgit v1.2.3 From cf46ed78046a03ef1a159b7d0b373b59d8e69042 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Fri, 29 Apr 2022 15:12:55 -0400 Subject: Bump base upper bound --- haddock.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock.cabal b/haddock.cabal index 37cd5a42..088209fc 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -66,7 +66,7 @@ executable haddock -- haddock typically only supports a single GHC major version build-depends: - base ^>= 4.13.0.0 || ^>= 4.14.0.0 || ^>= 4.15.0.0 || ^>= 4.16.0.0 + base ^>= 4.13.0.0 || ^>= 4.14.0.0 || ^>= 4.15.0.0 || ^>= 4.16.0.0 || ^>= 4.17.0.0 if flag(in-ghc-tree) hs-source-dirs: haddock-api/src, haddock-library/src -- cgit v1.2.3 From 2368e9329e6600b46000abd24ec00b7e27bcae75 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Fri, 29 Apr 2022 23:58:38 -0400 Subject: Update test output --- html-test/ref/Instances.html | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html index 109e866c..e99f82e4 100644 --- a/html-test/ref/Instances.html +++ b/html-test/ref/Instances.html @@ -262,9 +262,7 @@ > Foo List [] # Bar List (a, a) [] (a, a) # Date: Sun, 24 Jul 2022 07:45:59 -0400 Subject: Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. --- .hlint.yaml | 1 - .../src/Haddock/Backends/Hyperlinker/Renderer.hs | 2 +- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 2 +- haddock-api/src/Haddock/Backends/Xhtml/Layout.hs | 2 +- haddock-api/src/Haddock/GhcUtils.hs | 2 +- haddock-api/src/Haddock/Interface/Create.hs | 2 +- haddock-api/src/Haddock/Utils/Json.hs | 2 +- haddock-test/src/Test/Haddock.hs | 8 ++-- hypsrc-test/ref/src/Operators.html | 56 +++++++--------------- hypsrc-test/src/Operators.hs | 4 +- 10 files changed, 29 insertions(+), 52 deletions(-) diff --git a/.hlint.yaml b/.hlint.yaml index 4a0c8ddc..b57c494f 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -10,7 +10,6 @@ - ignore: {name: "Move brackets to avoid $"} # 7 hints - ignore: {name: "Move guards forward"} # 1 hint - ignore: {name: "Move map inside list comprehension"} # 2 hints -- ignore: {name: "Redundant $"} # 11 hints - ignore: {name: "Redundant <$>"} # 3 hints - ignore: {name: "Redundant bracket"} # 44 hints - ignore: {name: "Redundant id"} # 1 hint diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs index a8a51e5d..7fa5a443 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs @@ -142,7 +142,7 @@ richToken srcs details Token{..} contexts = concatMap (Set.elems . identInfo) . Map.elems . nodeIdentifiers $ details -- pick an arbitrary non-evidence identifier to hyperlink with - identDet = Map.lookupMin $ Map.filter notEvidence $ nodeIdentifiers $ details + identDet = Map.lookupMin $ Map.filter notEvidence $ nodeIdentifiers details notEvidence = not . any isEvidenceContext . identInfo -- If we have name information, we can make links diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 8de1b1b8..2c3da7a9 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -725,7 +725,7 @@ ppInstanceSigs links splice unicode qual sigs = do L _ rtyp = dropWildCards typ -- Instance methods signatures are synified and thus don't have a useful -- SrcSpan value. Use the methods name location instead. - return $ ppSimpleSig links splice unicode qual HideEmptyContexts (getLocA $ head $ lnames) names rtyp + return $ ppSimpleSig links splice unicode qual HideEmptyContexts (getLocA $ head lnames) names rtyp lookupAnySubdoc :: Eq id1 => id1 -> [(id1, DocForDecl id2)] -> DocForDecl id2 diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index 18405db8..575249ad 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -220,7 +220,7 @@ subOrphanInstances pkg qual lnks splice = maybe noHtml wrap . instTable where wrap = ((h1 << "Orphan instances") +++) instTable = fmap (thediv ! [ identifier ("section." ++ id_) ] <<) . subTableSrc pkg qual lnks splice - id_ = makeAnchorId $ "orphans" + id_ = makeAnchorId "orphans" subInstHead :: String -- ^ Instance unique id (for anchor generation) diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index ebddb397..19494c8e 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -474,7 +474,7 @@ instance Parent (ConDecl GhcRn) where instance Parent (TyClDecl GhcRn) where children d | isDataDecl d = map unLoc $ concatMap (getConNames . unLoc) - $ (dd_cons . tcdDataDefn) $ d + $ (dd_cons . tcdDataDefn) d | isClassDecl d = map (unLoc . fdLName . unLoc) (tcdATs d) ++ [ unLoc n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns ] diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index b3796906..17b9f367 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -331,7 +331,7 @@ mkAliasMap state impDecls = M.fromList $ mapMaybe (\(SrcLoc.L _ impDecl) -> do SrcLoc.L _ alias <- ideclAs impDecl - return $ + return (lookupModuleDyn state -- TODO: This is supremely dodgy, because in general the -- UnitId isn't going to look anything like the package diff --git a/haddock-api/src/Haddock/Utils/Json.hs b/haddock-api/src/Haddock/Utils/Json.hs index 6bcd38fa..0a796b4a 100644 --- a/haddock-api/src/Haddock/Utils/Json.hs +++ b/haddock-api/src/Haddock/Utils/Json.hs @@ -400,7 +400,7 @@ parseIntegralFromDouble d = let r = toRational d x = truncate r in if toRational x == r - then pure $ x + then pure x else fail $ "unexpected floating number " <> show d parseIntegral :: Integral a => String -> Value -> Parser a diff --git a/haddock-test/src/Test/Haddock.hs b/haddock-test/src/Test/Haddock.hs index 1019e815..fe547ad5 100644 --- a/haddock-test/src/Test/Haddock.hs +++ b/haddock-test/src/Test/Haddock.hs @@ -89,9 +89,9 @@ runHaddock cfg@(Config { .. }) = do , pure $ "--odir=" ++ outDir cfgDirConfig tpkg , tpkgFiles tpkg ] - , pcEnv = Just $ cfgEnv - , pcStdOut = Just $ haddockStdOut - , pcStdErr = Just $ haddockStdOut + , pcEnv = Just cfgEnv + , pcStdOut = Just haddockStdOut + , pcStdErr = Just haddockStdOut } let msg = "Failed to run Haddock on test package '" ++ tpkgName tpkg ++ "'" @@ -159,7 +159,7 @@ diffFile cfg diff file = do hFlush stdout handle <- runProcess' diff $ processConfig { pcArgs = [outFile', refFile'] - , pcStdOut = Just $ stdout + , pcStdOut = Just stdout } waitForProcess handle >> return () where diff --git a/hypsrc-test/ref/src/Operators.html b/hypsrc-test/ref/src/Operators.html index 04006a0d..8519d9de 100644 --- a/hypsrc-test/ref/src/Operators.html +++ b/hypsrc-test/ref/src/Operators.html @@ -33,11 +33,6 @@ - - ((a, b) -> c -> (a, b)) -> (a, b) -> c -> (a, b) -forall a b. (a -> b) -> a -> b -$ ( [a] -> [a] a +++ b = a ++ b ++ a @@ -18,6 +17,5 @@ a */\* b = concatMap (*** b) a (**/\**) :: [[a]] -> [[a]] -> [[a]] a **/\** b = zipWith (*/\*) [a +++ b] (a $$$ b) - (#.#) :: a -> b -> (c -> (a, b)) -a #.# b = const $ (a, b) +a #.# b = const (a, b) -- cgit v1.2.3 From 2036454bf6a86e14d9da9da5a19ce49ff3975fd7 Mon Sep 17 00:00:00 2001 From: Jade Lovelace Date: Sat, 7 May 2022 08:42:08 -0700 Subject: Fix hyperlinks to external items and modules (#1482) Fixes #1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by #977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) --- .../src/Haddock/Backends/Hyperlinker/Renderer.hs | 17 +++++++++++++---- 1 file changed, 13 insertions(+), 4 deletions(-) diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs index 12f37ced..d77990d1 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs @@ -24,6 +24,7 @@ import System.FilePath.Posix (()) import qualified Data.Map as Map import qualified Data.Set as Set +import qualified Data.List as List import Text.XHtml (Html, HtmlAttr, (!)) import qualified Text.XHtml as Html @@ -249,14 +250,20 @@ hyperlink (srcs, srcs') ident = case ident of Left name -> externalModHyperlink name where + -- In a Nix environment, we have file:// URLs with absolute paths + makeHyperlinkUrl url | List.isPrefixOf "file://" url = url + makeHyperlinkUrl url = ".." url + internalHyperlink name content = Html.anchor content ! [ Html.href $ "#" ++ internalAnchorIdent name ] externalNameHyperlink name content = case Map.lookup mdl srcs of Just SrcLocal -> Html.anchor content ! [ Html.href $ hypSrcModuleNameUrl mdl name ] - Just (SrcExternal path) -> Html.anchor content ! - [ Html.href $ spliceURL Nothing (Just mdl) (Just name) Nothing (".." path) ] + Just (SrcExternal path) -> + let hyperlinkUrl = makeHyperlinkUrl path hypSrcModuleNameUrl mdl name + in Html.anchor content ! + [ Html.href $ spliceURL Nothing (Just mdl) (Just name) Nothing hyperlinkUrl ] Nothing -> content where mdl = nameModule name @@ -265,8 +272,10 @@ hyperlink (srcs, srcs') ident = case ident of case Map.lookup moduleName srcs' of Just SrcLocal -> Html.anchor content ! [ Html.href $ hypSrcModuleUrl' moduleName ] - Just (SrcExternal path) -> Html.anchor content ! - [ Html.href $ spliceURL' Nothing (Just moduleName) Nothing Nothing (".." path) ] + Just (SrcExternal path) -> + let hyperlinkUrl = makeHyperlinkUrl path hypSrcModuleUrl' moduleName + in Html.anchor content ! + [ Html.href $ spliceURL' Nothing (Just moduleName) Nothing Nothing hyperlinkUrl ] Nothing -> content -- cgit v1.2.3 From 06b72bd9becf87e5396bb640289b63679a39ab3c Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Fri, 5 Aug 2022 19:07:23 -0400 Subject: Clean up build and testsuite for GHC 9.4 --- haddock-api/haddock-api.cabal | 14 +- haddock-api/src/Haddock.hs | 1 - haddock-api/src/Haddock/Backends/Hyperlinker.hs | 2 - haddock-api/src/Haddock/Interface.hs | 9 +- haddock-api/src/Haddock/Interface/Create.hs | 5 +- haddock-api/src/Haddock/Interface/LexParseRn.hs | 1 - haddock-api/src/Haddock/Interface/Specialize.hs | 1 - haddock-api/src/Haddock/InterfaceFile.hs | 13 -- html-test/ref/Bug1004.html | 200 ++++++------------------ html-test/ref/Bug310.html | 34 ---- html-test/ref/Bug548.html | 40 ++--- 11 files changed, 64 insertions(+), 256 deletions(-) diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index be84f8ce..206b9aa2 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -1,10 +1,10 @@ -cabal-version: 2.0 +cabal-version: 3.0 name: haddock-api -version: 2.26.1 +version: 2.27.0 synopsis: A documentation-generation tool for Haskell libraries description: Haddock is a documentation-generation tool for Haskell libraries -license: BSD2 +license: BSD-2-Clause license-file: LICENSE author: Simon Marlow, David Waern maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk @@ -13,7 +13,7 @@ bug-reports: https://github.com/haskell/haddock/issues copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.2.* +tested-with: GHC==9.4.* extra-source-files: CHANGES.md @@ -44,9 +44,9 @@ library -- this package typically supports only single major versions build-depends: base ^>= 4.16.0 - , ghc ^>= 9.3 + , ghc ^>= 9.4 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.10.0 + , haddock-library ^>= 1.10 , xhtml ^>= 3000.2.2 , parsec ^>= 3.1.13.0 @@ -180,7 +180,7 @@ test-suite spec Haddock.Backends.Hyperlinker.Parser Haddock.Backends.Hyperlinker.Types - build-depends: ghc ^>= 9.3 + build-depends: ghc ^>= 9.4 , ghc-paths ^>= 0.1.0.12 , haddock-library ^>= 1.10.0 , xhtml ^>= 3000.2.2 diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 989ca03f..ea664bcf 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -80,7 +80,6 @@ import GHC.Utils.Error import GHC.Utils.Logger import GHC.Types.Name.Cache import GHC.Unit -import GHC.Unit.State (lookupUnit) import GHC.Utils.Panic (handleGhcException) import GHC.Data.FastString diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs index 89828e30..9316da6d 100644 --- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs +++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs @@ -26,8 +26,6 @@ import GHC.Types.SrcLoc ( realSrcLocSpan, mkRealSrcLoc, srcSpanFile ) import Data.Map as M import GHC.Data.FastString ( mkFastString ) import GHC.Unit.Module ( Module, moduleName ) -import GHC.Types.Name.Cache ( initNameCache ) -import GHC.Types.Unique.Supply ( mkSplitUniqSupply ) -- | Generate hyperlinked source for given interfaces. diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 19113107..92b727ac 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -46,7 +46,7 @@ import Haddock.Types (DocOption (..), Documentation (..), ExportItem (..), Iface import Haddock.Utils (Verbosity (..), normal, out, verbose) import Control.Monad (unless, when) -import Control.Monad.IO.Class (MonadIO, liftIO) +import Control.Monad.IO.Class (MonadIO) import Data.IORef (atomicModifyIORef', newIORef, readIORef) import Data.List (foldl', isPrefixOf, nub) import Text.Printf (printf) @@ -54,7 +54,6 @@ import qualified Data.Map as Map import qualified Data.Set as Set import GHC hiding (verbosity) -import GHC.Data.FastString (unpackFS) import GHC.Data.Graph.Directed import GHC.Driver.Env import GHC.Driver.Monad (modifySession, withTimingM) @@ -64,13 +63,7 @@ import GHC.Plugins import GHC.Tc.Types (TcGblEnv (..), TcM) import GHC.Tc.Utils.Env (tcLookupGlobal) import GHC.Tc.Utils.Monad (getTopEnv, setGblEnv) -import GHC.Types.Name (nameIsFromExternalPackage, nameOccName) -import GHC.Types.Name.Occurrence (isTcOcc) -import GHC.Types.Name.Reader (globalRdrEnvElts, greMangledName, unQualOK) -import GHC.Unit.Module.Env (ModuleSet, emptyModuleSet, mkModuleSet, unionModuleSet) import GHC.Unit.Module.Graph -import GHC.Unit.Module.ModSummary (isBootSummary) -import GHC.Unit.Types (IsBootInterface (..)) import GHC.Utils.Error (withTiming) #if defined(mingw32_HOST_OS) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index b832128f..e3c4a529 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -54,7 +54,7 @@ import Data.Traversable (for) import GHC hiding (lookupName) import GHC.Core.Class (ClassMinimalDef, classMinimalDef) import GHC.Core.ConLike (ConLike (..)) -import GHC.Data.FastString (bytesFS, unpackFS) +import GHC.Data.FastString (unpackFS) import GHC.Driver.Ppr (showSDoc) import GHC.HsToCore.Docs hiding (mkMaps, unionArgMaps) import GHC.IORef (readIORef) @@ -1137,8 +1137,7 @@ extractDecl declMap name decl _ -> Left "internal: extractDecl (ClsInstD)" _ -> Left ("extractDecl: Unhandled decl for " ++ getOccString name) -extractPatternSyn :: HasCallStack - => Name -> Name +extractPatternSyn :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] -> Either ErrMsg (LSig GhcRn) extractPatternSyn nm t tvs cons = diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 4e1964af..455f3314 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -39,7 +39,6 @@ import GHC.Parser.PostProcess import GHC.Driver.Ppr ( showPpr, showSDoc ) import GHC.Types.Name.Reader import GHC.Data.EnumSet as EnumSet -import GHC.Utils.Trace processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString] -> ErrMsgM (Maybe (MDoc Name)) diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs index d1164858..ca6b9e74 100644 --- a/haddock-api/src/Haddock/Interface/Specialize.hs +++ b/haddock-api/src/Haddock/Interface/Specialize.hs @@ -16,7 +16,6 @@ import Haddock.Syb import Haddock.Types import GHC -import GHC.Types.Basic ( PromotionFlag(..) ) import GHC.Types.Name import GHC.Data.FastString import GHC.Builtin.Types ( listTyConName, unrestrictedFunTyConName ) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index f9861708..e6db49c0 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -309,19 +309,6 @@ putInterfaceFile_ bh (InterfaceFile env info ifaces) = do put_ bh info put_ bh ifaces -getInterfaceFile :: BinHandle -> Word16 -> IO InterfaceFile -getInterfaceFile bh v | v <= 38 = do - env <- get bh - let info = PackageInfo (PackageName mempty) (makeVersion []) - ifaces <- get bh - return (InterfaceFile env info ifaces) -getInterfaceFile bh _ = do - env <- get bh - info <- get bh - ifaces <- get bh - return (InterfaceFile env info ifaces) - - instance Binary InstalledInterface where put_ bh (InstalledInterface modu is_sig info docMap argMap exps visExps opts fixMap) = do diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html index 9fe6f84e..bbe2f599 100644 --- a/html-test/ref/Bug1004.html +++ b/html-test/ref/Bug1004.html @@ -48,26 +48,6 @@ >

    Bug1004

    Synopsis

    Documentation

    ) (a :: k) #

    Lifted product of functors.

    Constructors

    Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.16.0.0

     Product f g a)

    Since: base-4.16.0.0

     Product f g a)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.9.0.0

     Type)

    Since: base-4.9.0.0

     Product f g a)

    Since: base-4.9.0.0

     

    Bug310

    Synopsis

    Documentation

    Natural where ... infixl 6 #

    Addition of type-level naturals.

    Since: base-4.7.0.0

    WrappedArrow a b)

    Since: base-2.1

     WrappedArrow a b)

    Since: base-2.1

     WrappedArrow a b)

    Since: base-2.1

     Type)

    Since: base-4.7.0.0

     WrappedArrow a b c)

    Since: base-4.7.0.0

      Date: Fri, 5 Aug 2022 22:51:57 +0200 Subject: Bump the versions --- cabal.project | 4 ++-- haddock-api/haddock-api.cabal | 4 ++-- haddock-library/haddock-library.cabal | 4 ++-- haddock-test/haddock-test.cabal | 6 +++--- haddock.cabal | 6 +++--- 5 files changed, 12 insertions(+), 12 deletions(-) diff --git a/cabal.project b/cabal.project index 529b2250..e89a2cd5 100644 --- a/cabal.project +++ b/cabal.project @@ -5,7 +5,7 @@ packages: ./ ./haddock-library ./haddock-test -with-compiler: ghc-head +with-compiler: ghc-9.4 allow-newer: ghc-paths:Cabal, @@ -20,4 +20,4 @@ package haddock-api tests: False -- Pinning the index-state helps to make reasonably CI deterministic -index-state: 2021-01-24T12:09:34Z +index-state: 2022-08-05T20:43:48Z diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal index 206b9aa2..5923ba37 100644 --- a/haddock-api/haddock-api.cabal +++ b/haddock-api/haddock-api.cabal @@ -46,7 +46,7 @@ library build-depends: base ^>= 4.16.0 , ghc ^>= 9.4 , ghc-paths ^>= 0.1.0.9 - , haddock-library ^>= 1.10 + , haddock-library ^>= 1.11 , xhtml ^>= 3000.2.2 , parsec ^>= 3.1.13.0 @@ -182,7 +182,7 @@ test-suite spec build-depends: ghc ^>= 9.4 , ghc-paths ^>= 0.1.0.12 - , haddock-library ^>= 1.10.0 + , haddock-library ^>= 1.11 , xhtml ^>= 3000.2.2 , hspec ^>= 2.9 , parsec ^>= 3.1.13.0 diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index 9a868725..2e015f2a 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -1,6 +1,6 @@ -cabal-version: 2.2 +cabal-version: 3.0 name: haddock-library -version: 1.10.0 +version: 1.11.0 synopsis: Library exposing some functionality of Haddock. description: Haddock is a documentation-generation tool for Haskell diff --git a/haddock-test/haddock-test.cabal b/haddock-test/haddock-test.cabal index df6c4474..4e3bfd29 100644 --- a/haddock-test/haddock-test.cabal +++ b/haddock-test/haddock-test.cabal @@ -1,8 +1,8 @@ -cabal-version: >= 1.10 +cabal-version: 3.0 name: haddock-test version: 0.0.1 synopsis: Test utilities for Haddock -license: BSD2 +license: BSD-2-Clause author: Simon Marlow, David Waern maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ @@ -10,7 +10,7 @@ bug-reports: https://github.com/haskell/haddock/issues copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.0.* +tested-with: GHC==9.4.* stability: experimental library diff --git a/haddock.cabal b/haddock.cabal index d4d4375f..64ec9699 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -1,6 +1,6 @@ -cabal-version: 2.4 +cabal-version: 3.0 name: haddock -version: 2.26.1 +version: 2.27.0 synopsis: A documentation-generation tool for Haskell libraries description: This is Haddock, a tool for automatically generating documentation @@ -150,7 +150,7 @@ executable haddock else -- in order for haddock's advertised version number to have proper meaning, -- we pin down to a single haddock-api version. - build-depends: haddock-api == 2.26.1 + build-depends: haddock-api == 2.27.0 test-suite html-test type: exitcode-stdio-1.0 -- cgit v1.2.3 From f07a4059efcde05fd26b33a8c902930d3ad90379 Mon Sep 17 00:00:00 2001 From: Ben Gamari Date: Sat, 6 Aug 2022 22:57:21 -0400 Subject: html-test: Testsuite changes for GHC 9.4.1 --- html-test/ref/Bug1004.html | 200 +++++++++++++++++++++++++++++++++++---------- html-test/ref/Bug310.html | 34 ++++++++ html-test/ref/Bug548.html | 40 ++++++--- 3 files changed, 220 insertions(+), 54 deletions(-) diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html index bbe2f599..9fe6f84e 100644 --- a/html-test/ref/Bug1004.html +++ b/html-test/ref/Bug1004.html @@ -48,6 +48,26 @@ >

    Bug1004

    Synopsis

    Documentation

    ) (a :: k) #

    Lifted product of functors.

    Constructors

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.16.0.0

    Product f g a) 

    Since: base-4.16.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Type) 

    Since: base-4.9.0.0

    Product f g a) 

    Since: base-4.9.0.0

    Bug310

    Synopsis

    Documentation

    Natural where ... infixl 6 #

    Addition of type-level naturals.

    Since: base-4.7.0.0

    WrappedArrow a b) 

    Since: base-2.1

    WrappedArrow a b) 

    Since: base-2.1

    WrappedArrow a b) 

    Since: base-2.1

    Type) 

    Since: base-4.7.0.0

    WrappedArrow a b c) 

    Since: base-4.7.0.0

    Date: Mon, 15 Aug 2022 14:09:50 -0400 Subject: doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. --- doc/common-errors.rst | 2 +- doc/markup.rst | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/doc/common-errors.rst b/doc/common-errors.rst index 9afa4ea7..504ee886 100644 --- a/doc/common-errors.rst +++ b/doc/common-errors.rst @@ -7,7 +7,7 @@ Common Errors This is probably caused by the ``-- | xxx`` comment not following a declaration. I.e. use ``-- xxx`` instead. See :ref:`top-level-declaration`. ``parse error on input ‘-- $ xxx’`` ----------------------------------- +----------------------------------- You've probably commented out code like:: diff --git a/doc/markup.rst b/doc/markup.rst index 55ae3cb3..bae615cb 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -950,8 +950,8 @@ apostrophes themselves: to hyperlink ``foo'`` one would simply type -- | A prefix operator @'(++)'@ and an infix identifier @'`elem`'@. -Emphasis, Bold and Monospaced styled Text -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Emphasis, Bold and Monospaced Styled Text +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Text can be emphasized, made bold (strong) or monospaced (typewriter font) by surrounding it with slashes, double-underscores or at-symbols: :: -- cgit v1.2.3