diff options
Diffstat (limited to 'haddock-api/src/Haddock/Types.hs')
-rw-r--r-- | haddock-api/src/Haddock/Types.hs | 90 |
1 files changed, 40 insertions, 50 deletions
diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index cb4a4bcc..3ad90912 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -1,8 +1,8 @@ {-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving, TypeFamilies, RecordWildCards #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types] - -- in module GHC.PlaceHolder {-# OPTIONS_GHC -fno-warn-orphans #-} + ----------------------------------------------------------------------------- -- | -- Module : Haddock.Types @@ -101,6 +101,9 @@ data Interface = Interface -- names of subordinate declarations mapped to their parent declarations. , ifaceDeclMap :: !(Map Name [LHsDecl GhcRn]) + -- | Bundled pattern synonym declarations for specific types. + , ifaceBundledPatSynMap :: !(Map Name [Name]) + -- | Documentation of declarations originating from the module (including -- subordinates). , ifaceDocMap :: !(DocMap Name) @@ -156,49 +159,53 @@ type WarningMap = Map Name (Doc Name) data InstalledInterface = InstalledInterface { -- | The module represented by this interface. - instMod :: Module + instMod :: Module -- | Is this a signature? - , instIsSig :: Bool + , instIsSig :: Bool -- | Textual information about the module. - , instInfo :: HaddockModInfo Name + , instInfo :: HaddockModInfo Name -- | Documentation of declarations originating from the module (including -- subordinates). - , instDocMap :: DocMap Name + , instDocMap :: DocMap Name - , instArgMap :: ArgMap Name + , instArgMap :: ArgMap Name -- | All names exported by this module. - , instExports :: [Name] + , instExports :: [Name] -- | All \"visible\" names exported by the module. -- A visible name is a name that will show up in the documentation of the -- module. - , instVisibleExports :: [Name] + , instVisibleExports :: [Name] -- | Haddock options for this module (prune, ignore-exports, etc). - , instOptions :: [DocOption] + , instOptions :: [DocOption] + + , instSubMap :: Map Name [Name] - , instSubMap :: Map Name [Name] - , instFixMap :: Map Name Fixity + , instBundledPatSynMap :: Map Name [Name] + + , instFixMap :: Map Name Fixity } -- | Convert an 'Interface' to an 'InstalledInterface' toInstalledIface :: Interface -> InstalledInterface toInstalledIface interface = InstalledInterface - { instMod = ifaceMod interface - , instIsSig = ifaceIsSig interface - , instInfo = ifaceInfo interface - , instDocMap = ifaceDocMap interface - , instArgMap = ifaceArgMap interface - , instExports = ifaceExports interface - , instVisibleExports = ifaceVisibleExports interface - , instOptions = ifaceOptions interface - , instSubMap = ifaceSubMap interface - , instFixMap = ifaceFixMap interface + { instMod = ifaceMod interface + , instIsSig = ifaceIsSig interface + , instInfo = ifaceInfo interface + , instDocMap = ifaceDocMap interface + , instArgMap = ifaceArgMap interface + , instExports = ifaceExports interface + , instVisibleExports = ifaceVisibleExports interface + , instOptions = ifaceOptions interface + , instSubMap = ifaceSubMap interface + , instBundledPatSynMap = ifaceBundledPatSynMap interface + , instFixMap = ifaceFixMap interface } @@ -215,6 +222,9 @@ data ExportItem name -- | A declaration. expItemDecl :: !(LHsDecl name) + -- | Bundled patterns for a data type declaration + , expItemPats :: ![(HsDecl name, DocForDecl (IdP name))] + -- | Maybe a doc comment, and possibly docs for arguments (if this -- decl is a function or type-synonym). , expItemMbDoc :: !(DocForDecl (IdP name)) @@ -427,6 +437,8 @@ type LDoc id = Located (Doc id) type Doc id = DocH (ModuleName, OccName) id type MDoc id = MetaDoc (ModuleName, OccName) id +type DocMarkup id a = DocMarkupH (ModuleName, OccName) id a + instance (NFData a, NFData mod) => NFData (DocH mod a) where rnf doc = case doc of @@ -454,7 +466,7 @@ instance (NFData a, NFData mod) DocExamples a -> a `deepseq` () DocHeader a -> a `deepseq` () -#if !MIN_VERSION_GLASGOW_HASKELL(8,0,1,1) +#if !MIN_VERSION_ghc(8,0,2) -- These were added to GHC itself in 8.0.2 instance NFData Name where rnf x = seq x () instance NFData OccName where rnf x = seq x () @@ -478,34 +490,6 @@ exampleToString :: Example -> String exampleToString (Example expression result) = ">>> " ++ expression ++ "\n" ++ unlines result - -data DocMarkup id a = Markup - { markupEmpty :: a - , markupString :: String -> a - , markupParagraph :: a -> a - , markupAppend :: a -> a -> a - , markupIdentifier :: id -> a - , markupIdentifierUnchecked :: (ModuleName, OccName) -> a - , markupModule :: String -> a - , markupWarning :: a -> a - , markupEmphasis :: a -> a - , markupBold :: a -> a - , markupMonospaced :: a -> a - , markupUnorderedList :: [a] -> a - , markupOrderedList :: [a] -> a - , markupDefList :: [(a,a)] -> a - , markupCodeBlock :: a -> a - , markupHyperlink :: Hyperlink -> a - , markupAName :: String -> a - , markupPic :: Picture -> a - , markupMathInline :: String -> a - , markupMathDisplay :: String -> a - , markupProperty :: String -> a - , markupExample :: [Example] -> a - , markupHeader :: Header a -> a - } - - data HaddockModInfo name = HaddockModInfo { hmi_description :: Maybe (Doc name) , hmi_copyright :: Maybe String @@ -589,6 +573,12 @@ makeModuleQual qual aliases mdl = OptFullQual -> FullQual OptNoQual -> NoQual +-- | Whether to hide empty contexts +-- Since pattern synonyms have two contexts with different semantics, it is +-- important to all of them, even if one of them is empty. +data HideEmptyContexts + = HideEmptyContexts + | ShowEmptyToplevelContexts ----------------------------------------------------------------------------- -- * Error handling |