{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving, TypeFamilies, RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Haddock.Types
-- Copyright   :  (c) Simon Marlow      2003-2006,
--                    David Waern       2006-2009,
--                    Mateusz Kowalczyk 2013
-- License     :  BSD-like
--
-- Maintainer  :  haddock@projects.haskellorg
-- Stability   :  experimental
-- Portability :  portable
--
-- Types that are commonly used through-out Haddock. Some of the most
-- important types are defined here, like 'Interface' and 'DocName'.
-----------------------------------------------------------------------------
module Haddock.Types (
  module Haddock.Types
  , HsDocString, LHsDocString
  , Fixity(..)
  , module Documentation.Haddock.Types
 ) where

import Control.Exception
import Control.Arrow hiding ((<+>))
import Control.DeepSeq
import Control.Monad (ap)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Typeable (Typeable)
import Data.Map (Map)
import Data.Data (Data)
import Data.Void (Void)
import Documentation.Haddock.Types
import BasicTypes (Fixity(..), PromotionFlag(..))

import Exception (ExceptionMonad(..), ghandle)
import GHC
import DynFlags (Language)
import qualified GHC.LanguageExtensions as LangExt
import OccName
import Outputable hiding ((<>))

-----------------------------------------------------------------------------
-- * Convenient synonyms
-----------------------------------------------------------------------------


type IfaceMap      = Map Module Interface
type InstIfaceMap  = Map Module InstalledInterface  -- TODO: rename
type DocMap a      = Map Name (MDoc a)
type ArgMap a      = Map Name (Map Int (MDoc a))
type SubMap        = Map Name [Name]
type DeclMap       = Map Name [LHsDecl GhcRn]
type InstMap       = Map SrcSpan Name
type FixMap        = Map Name Fixity
type DocPaths      = (FilePath, Maybe FilePath) -- paths to HTML and sources


-----------------------------------------------------------------------------
-- * Interface
-----------------------------------------------------------------------------


-- | 'Interface' holds all information used to render a single Haddock page.
-- It represents the /interface/ of a module. The core business of Haddock
-- lies in creating this structure. Note that the record contains some fields
-- that are only used to create the final record, and that are not used by the
-- backends.
data Interface = Interface
  {
    -- | The module behind this interface.
    Interface -> Module
ifaceMod             :: !Module

    -- | Is this a signature?
  , Interface -> Bool
ifaceIsSig           :: !Bool

    -- | Original file name of the module.
  , Interface -> FilePath
ifaceOrigFilename    :: !FilePath

    -- | Textual information about the module.
  , Interface -> HaddockModInfo Name
ifaceInfo            :: !(HaddockModInfo Name)

    -- | Documentation header.
  , Interface -> Documentation Name
ifaceDoc             :: !(Documentation Name)

    -- | Documentation header with cross-reference information.
  , Interface -> Documentation DocName
ifaceRnDoc           :: !(Documentation DocName)

    -- | Haddock options for this module (prune, ignore-exports, etc).
  , Interface -> [DocOption]
ifaceOptions         :: ![DocOption]

    -- | Declarations originating from the module. Excludes declarations without
    -- names (instances and stand-alone documentation comments). Includes
    -- names of subordinate declarations mapped to their parent declarations.
  , Interface -> Map Name [LHsDecl GhcRn]
ifaceDeclMap         :: !(Map Name [LHsDecl GhcRn])

    -- | Documentation of declarations originating from the module (including
    -- subordinates).
  , Interface -> DocMap Name
ifaceDocMap          :: !(DocMap Name)
  , Interface -> ArgMap Name
ifaceArgMap          :: !(ArgMap Name)

    -- | Documentation of declarations originating from the module (including
    -- subordinates).
  , Interface -> DocMap DocName
ifaceRnDocMap        :: !(DocMap DocName)
  , Interface -> ArgMap DocName
ifaceRnArgMap        :: !(ArgMap DocName)

  , Interface -> Map Name Fixity
ifaceFixMap          :: !(Map Name Fixity)

  , Interface -> [ExportItem GhcRn]
ifaceExportItems     :: ![ExportItem GhcRn]
  , Interface -> [ExportItem DocNameI]
ifaceRnExportItems   :: ![ExportItem DocNameI]

    -- | All names exported by the module.
  , Interface -> [Name]
ifaceExports         :: ![Name]

    -- | All \"visible\" names exported by the module.
    -- A visible name is a name that will show up in the documentation of the
    -- module.
  , Interface -> [Name]
ifaceVisibleExports  :: ![Name]

    -- | Aliases of module imports as in @import A.B.C as C@.
  , Interface -> AliasMap
ifaceModuleAliases   :: !AliasMap

    -- | Instances exported by the module.
  , Interface -> [ClsInst]
ifaceInstances       :: ![ClsInst]
  , Interface -> [FamInst]
ifaceFamInstances    :: ![FamInst]

    -- | Orphan instances
  , Interface -> [DocInstance GhcRn]
ifaceOrphanInstances :: ![DocInstance GhcRn]
  , Interface -> [DocInstance DocNameI]
ifaceRnOrphanInstances :: ![DocInstance DocNameI]

    -- | The number of haddockable and haddocked items in the module, as a
    -- tuple. Haddockable items are the exports and the module itself.
  , Interface -> (Int, Int)
ifaceHaddockCoverage :: !(Int, Int)

    -- | Warnings for things defined in this module.
  , Interface -> WarningMap
ifaceWarningMap :: !WarningMap

    -- | Tokenized source code of module (avaliable if Haddock is invoked with
    -- source generation flag).
  , Interface -> Maybe FilePath
ifaceHieFile :: !(Maybe FilePath)
  , Interface -> DynFlags
ifaceDynFlags :: !DynFlags
  }

type WarningMap = Map Name (Doc Name)


-- | A subset of the fields of 'Interface' that we store in the interface
-- files.
data InstalledInterface = InstalledInterface
  {
    -- | The module represented by this interface.
    InstalledInterface -> Module
instMod              :: Module

    -- | Is this a signature?
  , InstalledInterface -> Bool
instIsSig            :: Bool

    -- | Textual information about the module.
  , InstalledInterface -> HaddockModInfo Name
instInfo             :: HaddockModInfo Name

    -- | Documentation of declarations originating from the module (including
    -- subordinates).
  , InstalledInterface -> DocMap Name
instDocMap           :: DocMap Name

  , InstalledInterface -> ArgMap Name
instArgMap           :: ArgMap Name

    -- | All names exported by this module.
  , InstalledInterface -> [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.
  , InstalledInterface -> [Name]
instVisibleExports   :: [Name]

    -- | Haddock options for this module (prune, ignore-exports, etc).
  , InstalledInterface -> [DocOption]
instOptions          :: [DocOption]

  , InstalledInterface -> Map Name Fixity
instFixMap           :: Map Name Fixity
  }


-- | Convert an 'Interface' to an 'InstalledInterface'
toInstalledIface :: Interface -> InstalledInterface
toInstalledIface :: Interface -> InstalledInterface
toInstalledIface Interface
interface = InstalledInterface :: Module
-> Bool
-> HaddockModInfo Name
-> DocMap Name
-> ArgMap Name
-> [Name]
-> [Name]
-> [DocOption]
-> Map Name Fixity
-> InstalledInterface
InstalledInterface
  { instMod :: Module
instMod              = Interface -> Module
ifaceMod              Interface
interface
  , instIsSig :: Bool
instIsSig            = Interface -> Bool
ifaceIsSig            Interface
interface
  , instInfo :: HaddockModInfo Name
instInfo             = Interface -> HaddockModInfo Name
ifaceInfo             Interface
interface
  , instDocMap :: DocMap Name
instDocMap           = Interface -> DocMap Name
ifaceDocMap           Interface
interface
  , instArgMap :: ArgMap Name
instArgMap           = Interface -> ArgMap Name
ifaceArgMap           Interface
interface
  , instExports :: [Name]
instExports          = Interface -> [Name]
ifaceExports          Interface
interface
  , instVisibleExports :: [Name]
instVisibleExports   = Interface -> [Name]
ifaceVisibleExports   Interface
interface
  , instOptions :: [DocOption]
instOptions          = Interface -> [DocOption]
ifaceOptions          Interface
interface
  , instFixMap :: Map Name Fixity
instFixMap           = Interface -> Map Name Fixity
ifaceFixMap           Interface
interface
  }


-----------------------------------------------------------------------------
-- * Export items & declarations
-----------------------------------------------------------------------------


data ExportItem name

  -- | An exported declaration.
  = ExportDecl
      {
        -- | A declaration.
        ExportItem name -> LHsDecl name
expItemDecl :: !(LHsDecl name)

        -- | Bundled patterns for a data type declaration
      , ExportItem name -> [(HsDecl name, DocForDecl (IdP name))]
expItemPats :: ![(HsDecl name, DocForDecl (IdP name))]

        -- | Maybe a doc comment, and possibly docs for arguments (if this
        -- decl is a function or type-synonym).
      , ExportItem name -> DocForDecl (IdP name)
expItemMbDoc :: !(DocForDecl (IdP name))

        -- | Subordinate names, possibly with documentation.
      , ExportItem name -> [(IdP name, DocForDecl (IdP name))]
expItemSubDocs :: ![(IdP name, DocForDecl (IdP name))]

        -- | Instances relevant to this declaration, possibly with
        -- documentation.
      , ExportItem name -> [DocInstance name]
expItemInstances :: ![DocInstance name]

        -- | Fixity decls relevant to this declaration (including subordinates).
      , ExportItem name -> [(IdP name, Fixity)]
expItemFixities :: ![(IdP name, Fixity)]

        -- | Whether the ExportItem is from a TH splice or not, for generating
        -- the appropriate type of Source link.
      , ExportItem name -> Bool
expItemSpliced :: !Bool
      }

  -- | An exported entity for which we have no documentation (perhaps because it
  -- resides in another package).
  | ExportNoDecl
      { ExportItem name -> IdP name
expItemName :: !(IdP name)

        -- | Subordinate names.
      , ExportItem name -> [IdP name]
expItemSubs :: ![IdP name]
      }

  -- | A section heading.
  | ExportGroup
      {
        -- | Section level (1, 2, 3, ...).
        ExportItem name -> Int
expItemSectionLevel :: !Int

        -- | Section id (for hyperlinks).
      , ExportItem name -> FilePath
expItemSectionId :: !String

        -- | Section heading text.
      , ExportItem name -> Doc (IdP name)
expItemSectionText :: !(Doc (IdP name))
      }

  -- | Some documentation.
  | ExportDoc !(MDoc (IdP name))

  -- | A cross-reference to another module.
  | ExportModule !Module

data Documentation name = Documentation
  { Documentation name -> Maybe (MDoc name)
documentationDoc :: Maybe (MDoc name)
  , Documentation name -> Maybe (Doc name)
documentationWarning :: !(Maybe (Doc name))
  } deriving a -> Documentation b -> Documentation a
(a -> b) -> Documentation a -> Documentation b
(forall a b. (a -> b) -> Documentation a -> Documentation b)
-> (forall a b. a -> Documentation b -> Documentation a)
-> Functor Documentation
forall a b. a -> Documentation b -> Documentation a
forall a b. (a -> b) -> Documentation a -> Documentation b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Documentation b -> Documentation a
$c<$ :: forall a b. a -> Documentation b -> Documentation a
fmap :: (a -> b) -> Documentation a -> Documentation b
$cfmap :: forall a b. (a -> b) -> Documentation a -> Documentation b
Functor


-- | Arguments and result are indexed by Int, zero-based from the left,
-- because that's the easiest to use when recursing over types.
type FnArgsDoc name = Map Int (MDoc name)
type DocForDecl name = (Documentation name, FnArgsDoc name)


noDocForDecl :: DocForDecl name
noDocForDecl :: DocForDecl name
noDocForDecl = (Maybe (MDoc name) -> Maybe (Doc name) -> Documentation name
forall name.
Maybe (MDoc name) -> Maybe (Doc name) -> Documentation name
Documentation Maybe (MDoc name)
forall a. Maybe a
Nothing Maybe (Doc name)
forall a. Maybe a
Nothing, Map Int (MDoc name)
forall a. Monoid a => a
mempty)


-----------------------------------------------------------------------------
-- * Cross-referencing
-----------------------------------------------------------------------------


-- | Type of environment used to cross-reference identifiers in the syntax.
type LinkEnv = Map Name Module

-- | An 'RdrName' tagged with some type/value namespace information.
data NsRdrName = NsRdrName
  { NsRdrName -> Namespace
namespace :: !Namespace
  , NsRdrName -> RdrName
rdrName :: !RdrName
  }

-- | Extends 'Name' with cross-reference information.
data DocName
  = Documented Name Module
     -- ^ This thing is part of the (existing or resulting)
     -- documentation. The 'Module' is the preferred place
     -- in the documentation to refer to.
  | Undocumented Name
     -- ^ This thing is not part of the (existing or resulting)
     -- documentation, as far as Haddock knows.
  deriving (DocName -> DocName -> Bool
(DocName -> DocName -> Bool)
-> (DocName -> DocName -> Bool) -> Eq DocName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocName -> DocName -> Bool
$c/= :: DocName -> DocName -> Bool
== :: DocName -> DocName -> Bool
$c== :: DocName -> DocName -> Bool
Eq, Typeable DocName
DataType
Constr
Typeable DocName
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> DocName -> c DocName)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c DocName)
-> (DocName -> Constr)
-> (DocName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c DocName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocName))
-> ((forall b. Data b => b -> b) -> DocName -> DocName)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> DocName -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> DocName -> r)
-> (forall u. (forall d. Data d => d -> u) -> DocName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DocName -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> DocName -> m DocName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DocName -> m DocName)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DocName -> m DocName)
-> Data DocName
DocName -> DataType
DocName -> Constr
(forall b. Data b => b -> b) -> DocName -> DocName
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DocName -> c DocName
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DocName
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DocName -> u
forall u. (forall d. Data d => d -> u) -> DocName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DocName -> m DocName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DocName -> m DocName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DocName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DocName -> c DocName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DocName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocName)
$cUndocumented :: Constr
$cDocumented :: Constr
$tDocName :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DocName -> m DocName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DocName -> m DocName
gmapMp :: (forall d. Data d => d -> m d) -> DocName -> m DocName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DocName -> m DocName
gmapM :: (forall d. Data d => d -> m d) -> DocName -> m DocName
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DocName -> m DocName
gmapQi :: Int -> (forall d. Data d => d -> u) -> DocName -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DocName -> u
gmapQ :: (forall d. Data d => d -> u) -> DocName -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DocName -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DocName -> r
gmapT :: (forall b. Data b => b -> b) -> DocName -> DocName
$cgmapT :: (forall b. Data b => b -> b) -> DocName -> DocName
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocName)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DocName)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DocName)
dataTypeOf :: DocName -> DataType
$cdataTypeOf :: DocName -> DataType
toConstr :: DocName -> Constr
$ctoConstr :: DocName -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DocName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DocName
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DocName -> c DocName
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DocName -> c DocName
$cp1Data :: Typeable DocName
Data)

data DocNameI

type instance IdP DocNameI = DocName


instance NamedThing DocName where
  getName :: DocName -> Name
getName (Documented Name
name Module
_) = Name
name
  getName (Undocumented Name
name) = Name
name

-- | Useful for debugging
instance Outputable DocName where
  ppr :: DocName -> SDoc
ppr = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> SDoc) -> (DocName -> Name) -> DocName -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocName -> Name
forall a. NamedThing a => a -> Name
getName

instance OutputableBndr DocName where
  pprBndr :: BindingSite -> DocName -> SDoc
pprBndr BindingSite
_ = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> SDoc) -> (DocName -> Name) -> DocName -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocName -> Name
forall a. NamedThing a => a -> Name
getName
  pprPrefixOcc :: DocName -> SDoc
pprPrefixOcc = Name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc (Name -> SDoc) -> (DocName -> Name) -> DocName -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocName -> Name
forall a. NamedThing a => a -> Name
getName
  pprInfixOcc :: DocName -> SDoc
pprInfixOcc = Name -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprInfixOcc (Name -> SDoc) -> (DocName -> Name) -> DocName -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocName -> Name
forall a. NamedThing a => a -> Name
getName

class NamedThing name => SetName name where

    setName :: Name -> name -> name


instance SetName Name where

    setName :: Name -> Name -> Name
setName Name
name' Name
_ = Name
name'


instance SetName DocName where

    setName :: Name -> DocName -> DocName
setName Name
name' (Documented Name
_ Module
mdl) = Name -> Module -> DocName
Documented Name
name' Module
mdl
    setName Name
name' (Undocumented Name
_) = Name -> DocName
Undocumented Name
name'

-- | Adds extra "wrapper" information to a name.
--
-- This is to work around the fact that most name types in GHC ('Name', 'RdrName',
-- 'OccName', ...) don't include backticks or parens.
data Wrap n
  = Unadorned { Wrap n -> n
unwrap :: n  }     -- ^ don't do anything to the name
  | Parenthesized { unwrap :: n }  -- ^ add parentheses around the name
  | Backticked { unwrap :: n }     -- ^ add backticks around the name
  deriving (Int -> Wrap n -> ShowS
[Wrap n] -> ShowS
Wrap n -> FilePath
(Int -> Wrap n -> ShowS)
-> (Wrap n -> FilePath) -> ([Wrap n] -> ShowS) -> Show (Wrap n)
forall n. Show n => Int -> Wrap n -> ShowS
forall n. Show n => [Wrap n] -> ShowS
forall n. Show n => Wrap n -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Wrap n] -> ShowS
$cshowList :: forall n. Show n => [Wrap n] -> ShowS
show :: Wrap n -> FilePath
$cshow :: forall n. Show n => Wrap n -> FilePath
showsPrec :: Int -> Wrap n -> ShowS
$cshowsPrec :: forall n. Show n => Int -> Wrap n -> ShowS
Show, a -> Wrap b -> Wrap a
(a -> b) -> Wrap a -> Wrap b
(forall a b. (a -> b) -> Wrap a -> Wrap b)
-> (forall a b. a -> Wrap b -> Wrap a) -> Functor Wrap
forall a b. a -> Wrap b -> Wrap a
forall a b. (a -> b) -> Wrap a -> Wrap b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Wrap b -> Wrap a
$c<$ :: forall a b. a -> Wrap b -> Wrap a
fmap :: (a -> b) -> Wrap a -> Wrap b
$cfmap :: forall a b. (a -> b) -> Wrap a -> Wrap b
Functor, Wrap a -> Bool
(a -> m) -> Wrap a -> m
(a -> b -> b) -> b -> Wrap a -> b
(forall m. Monoid m => Wrap m -> m)
-> (forall m a. Monoid m => (a -> m) -> Wrap a -> m)
-> (forall m a. Monoid m => (a -> m) -> Wrap a -> m)
-> (forall a b. (a -> b -> b) -> b -> Wrap a -> b)
-> (forall a b. (a -> b -> b) -> b -> Wrap a -> b)
-> (forall b a. (b -> a -> b) -> b -> Wrap a -> b)
-> (forall b a. (b -> a -> b) -> b -> Wrap a -> b)
-> (forall a. (a -> a -> a) -> Wrap a -> a)
-> (forall a. (a -> a -> a) -> Wrap a -> a)
-> (forall a. Wrap a -> [a])
-> (forall a. Wrap a -> Bool)
-> (forall a. Wrap a -> Int)
-> (forall a. Eq a => a -> Wrap a -> Bool)
-> (forall a. Ord a => Wrap a -> a)
-> (forall a. Ord a => Wrap a -> a)
-> (forall a. Num a => Wrap a -> a)
-> (forall a. Num a => Wrap a -> a)
-> Foldable Wrap
forall a. Eq a => a -> Wrap a -> Bool
forall a. Num a => Wrap a -> a
forall a. Ord a => Wrap a -> a
forall m. Monoid m => Wrap m -> m
forall a. Wrap a -> Bool
forall a. Wrap a -> Int
forall a. Wrap a -> [a]
forall a. (a -> a -> a) -> Wrap a -> a
forall m a. Monoid m => (a -> m) -> Wrap a -> m
forall b a. (b -> a -> b) -> b -> Wrap a -> b
forall a b. (a -> b -> b) -> b -> Wrap a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Wrap a -> a
$cproduct :: forall a. Num a => Wrap a -> a
sum :: Wrap a -> a
$csum :: forall a. Num a => Wrap a -> a
minimum :: Wrap a -> a
$cminimum :: forall a. Ord a => Wrap a -> a
maximum :: Wrap a -> a
$cmaximum :: forall a. Ord a => Wrap a -> a
elem :: a -> Wrap a -> Bool
$celem :: forall a. Eq a => a -> Wrap a -> Bool
length :: Wrap a -> Int
$clength :: forall a. Wrap a -> Int
null :: Wrap a -> Bool
$cnull :: forall a. Wrap a -> Bool
toList :: Wrap a -> [a]
$ctoList :: forall a. Wrap a -> [a]
foldl1 :: (a -> a -> a) -> Wrap a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Wrap a -> a
foldr1 :: (a -> a -> a) -> Wrap a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Wrap a -> a
foldl' :: (b -> a -> b) -> b -> Wrap a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Wrap a -> b
foldl :: (b -> a -> b) -> b -> Wrap a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Wrap a -> b
foldr' :: (a -> b -> b) -> b -> Wrap a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Wrap a -> b
foldr :: (a -> b -> b) -> b -> Wrap a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Wrap a -> b
foldMap' :: (a -> m) -> Wrap a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Wrap a -> m
foldMap :: (a -> m) -> Wrap a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Wrap a -> m
fold :: Wrap m -> m
$cfold :: forall m. Monoid m => Wrap m -> m
Foldable, Functor Wrap
Foldable Wrap
Functor Wrap
-> Foldable Wrap
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Wrap a -> f (Wrap b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Wrap (f a) -> f (Wrap a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Wrap a -> m (Wrap b))
-> (forall (m :: * -> *) a. Monad m => Wrap (m a) -> m (Wrap a))
-> Traversable Wrap
(a -> f b) -> Wrap a -> f (Wrap b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Wrap (m a) -> m (Wrap a)
forall (f :: * -> *) a. Applicative f => Wrap (f a) -> f (Wrap a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Wrap a -> m (Wrap b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Wrap a -> f (Wrap b)
sequence :: Wrap (m a) -> m (Wrap a)
$csequence :: forall (m :: * -> *) a. Monad m => Wrap (m a) -> m (Wrap a)
mapM :: (a -> m b) -> Wrap a -> m (Wrap b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Wrap a -> m (Wrap b)
sequenceA :: Wrap (f a) -> f (Wrap a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Wrap (f a) -> f (Wrap a)
traverse :: (a -> f b) -> Wrap a -> f (Wrap b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Wrap a -> f (Wrap b)
$cp2Traversable :: Foldable Wrap
$cp1Traversable :: Functor Wrap
Traversable)

-- | Useful for debugging
instance Outputable n => Outputable (Wrap n) where
  ppr :: Wrap n -> SDoc
ppr (Unadorned n
n)     = n -> SDoc
forall a. Outputable a => a -> SDoc
ppr n
n
  ppr (Parenthesized n
n) = [SDoc] -> SDoc
hcat [ Char -> SDoc
char Char
'(', n -> SDoc
forall a. Outputable a => a -> SDoc
ppr n
n, Char -> SDoc
char Char
')' ]
  ppr (Backticked n
n)    = [SDoc] -> SDoc
hcat [ Char -> SDoc
char Char
'`', n -> SDoc
forall a. Outputable a => a -> SDoc
ppr n
n, Char -> SDoc
char Char
'`' ]

showWrapped :: (a -> String) -> Wrap a -> String
showWrapped :: (a -> FilePath) -> Wrap a -> FilePath
showWrapped a -> FilePath
f (Unadorned a
n) = a -> FilePath
f a
n
showWrapped a -> FilePath
f (Parenthesized a
n) = FilePath
"(" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> FilePath
f a
n FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
")"
showWrapped a -> FilePath
f (Backticked a
n) = FilePath
"`" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> FilePath
f a
n FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"`"

instance HasOccName DocName where

    occName :: DocName -> OccName
occName = Name -> OccName
forall name. HasOccName name => name -> OccName
occName (Name -> OccName) -> (DocName -> Name) -> DocName -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocName -> Name
forall a. NamedThing a => a -> Name
getName

-----------------------------------------------------------------------------
-- * Instances
-----------------------------------------------------------------------------

-- | The three types of instances
data InstType name
  = ClassInst
      { InstType name -> [HsType name]
clsiCtx :: [HsType name]
      , InstType name -> LHsQTyVars name
clsiTyVars :: LHsQTyVars name
      , InstType name -> [Sig name]
clsiSigs :: [Sig name]
      , InstType name -> [PseudoFamilyDecl name]
clsiAssocTys :: [PseudoFamilyDecl name]
      }
  | TypeInst  (Maybe (HsType name)) -- ^ Body (right-hand side)
  | DataInst (TyClDecl name)        -- ^ Data constructors

instance (OutputableBndrId p)
         => Outputable (InstType (GhcPass p)) where
  ppr :: InstType (GhcPass p) -> SDoc
ppr (ClassInst { [Sig (GhcPass p)]
[HsType (GhcPass p)]
[PseudoFamilyDecl (GhcPass p)]
LHsQTyVars (GhcPass p)
clsiAssocTys :: [PseudoFamilyDecl (GhcPass p)]
clsiSigs :: [Sig (GhcPass p)]
clsiTyVars :: LHsQTyVars (GhcPass p)
clsiCtx :: [HsType (GhcPass p)]
clsiAssocTys :: forall name. InstType name -> [PseudoFamilyDecl name]
clsiSigs :: forall name. InstType name -> [Sig name]
clsiTyVars :: forall name. InstType name -> LHsQTyVars name
clsiCtx :: forall name. InstType name -> [HsType name]
.. }) = FilePath -> SDoc
text FilePath
"ClassInst"
      SDoc -> SDoc -> SDoc
<+> [HsType (GhcPass p)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [HsType (GhcPass p)]
clsiCtx
      SDoc -> SDoc -> SDoc
<+> LHsQTyVars (GhcPass p) -> SDoc
forall a. Outputable a => a -> SDoc
ppr LHsQTyVars (GhcPass p)
clsiTyVars
      SDoc -> SDoc -> SDoc
<+> [Sig (GhcPass p)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Sig (GhcPass p)]
clsiSigs
  ppr (TypeInst  Maybe (HsType (GhcPass p))
a) = FilePath -> SDoc
text FilePath
"TypeInst"  SDoc -> SDoc -> SDoc
<+> Maybe (HsType (GhcPass p)) -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe (HsType (GhcPass p))
a
  ppr (DataInst  TyClDecl (GhcPass p)
a) = FilePath -> SDoc
text FilePath
"DataInst"  SDoc -> SDoc -> SDoc
<+> TyClDecl (GhcPass p) -> SDoc
forall a. Outputable a => a -> SDoc
ppr TyClDecl (GhcPass p)
a


-- | Almost the same as 'FamilyDecl' except for type binders.
--
-- In order to perform type specialization for class instances, we need to
-- substitute class variables to appropriate type. However, type variables in
-- associated type are specified using 'LHsTyVarBndrs' instead of 'HsType'.
-- This makes type substitution impossible and to overcome this issue,
-- 'PseudoFamilyDecl' type is introduced.
data PseudoFamilyDecl name = PseudoFamilyDecl
    { PseudoFamilyDecl name -> FamilyInfo name
pfdInfo :: FamilyInfo name
    , PseudoFamilyDecl name -> Located (IdP name)
pfdLName :: Located (IdP name)
    , PseudoFamilyDecl name -> [LHsType name]
pfdTyVars :: [LHsType name]
    , PseudoFamilyDecl name -> LFamilyResultSig name
pfdKindSig :: LFamilyResultSig name
    }


mkPseudoFamilyDecl :: FamilyDecl (GhcPass p) -> PseudoFamilyDecl (GhcPass p)
mkPseudoFamilyDecl :: FamilyDecl (GhcPass p) -> PseudoFamilyDecl (GhcPass p)
mkPseudoFamilyDecl (FamilyDecl { Maybe (LInjectivityAnn (GhcPass p))
FamilyInfo (GhcPass p)
LHsQTyVars (GhcPass p)
XCFamilyDecl (GhcPass p)
LexicalFixity
LFamilyResultSig (GhcPass p)
Located (IdP (GhcPass p))
fdExt :: forall pass. FamilyDecl pass -> XCFamilyDecl pass
fdInfo :: forall pass. FamilyDecl pass -> FamilyInfo pass
fdLName :: forall pass. FamilyDecl pass -> Located (IdP pass)
fdTyVars :: forall pass. FamilyDecl pass -> LHsQTyVars pass
fdFixity :: forall pass. FamilyDecl pass -> LexicalFixity
fdResultSig :: forall pass. FamilyDecl pass -> LFamilyResultSig pass
fdInjectivityAnn :: forall pass. FamilyDecl pass -> Maybe (LInjectivityAnn pass)
fdInjectivityAnn :: Maybe (LInjectivityAnn (GhcPass p))
fdResultSig :: LFamilyResultSig (GhcPass p)
fdFixity :: LexicalFixity
fdTyVars :: LHsQTyVars (GhcPass p)
fdLName :: Located (IdP (GhcPass p))
fdInfo :: FamilyInfo (GhcPass p)
fdExt :: XCFamilyDecl (GhcPass p)
.. }) = PseudoFamilyDecl :: forall name.
FamilyInfo name
-> Located (IdP name)
-> [LHsType name]
-> LFamilyResultSig name
-> PseudoFamilyDecl name
PseudoFamilyDecl
    { pfdInfo :: FamilyInfo (GhcPass p)
pfdInfo = FamilyInfo (GhcPass p)
fdInfo
    , pfdLName :: Located (IdP (GhcPass p))
pfdLName = Located (IdP (GhcPass p))
fdLName
    , pfdTyVars :: [LHsType (GhcPass p)]
pfdTyVars = [ SrcSpan -> HsType (GhcPass p) -> LHsType (GhcPass p)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (HsTyVarBndr (GhcPass p) -> HsType (GhcPass p)
forall pass.
(XTyVar pass ~ NoExtField, XKindSig pass ~ NoExtField,
 XXTyVarBndr pass ~ NoExtCon) =>
HsTyVarBndr pass -> HsType pass
mkType HsTyVarBndr (GhcPass p)
bndr) | L SrcSpan
loc HsTyVarBndr (GhcPass p)
bndr <- LHsQTyVars (GhcPass p)
-> [GenLocated SrcSpan (HsTyVarBndr (GhcPass p))]
forall pass. LHsQTyVars pass -> [LHsTyVarBndr pass]
hsq_explicit LHsQTyVars (GhcPass p)
fdTyVars ]
    , pfdKindSig :: LFamilyResultSig (GhcPass p)
pfdKindSig = LFamilyResultSig (GhcPass p)
fdResultSig
    }
  where
    mkType :: HsTyVarBndr pass -> HsType pass
mkType (KindedTyVar XKindedTyVar pass
_ (L SrcSpan
loc IdP pass
name) LHsKind pass
lkind) =
        XKindSig pass -> LHsKind pass -> LHsKind pass -> HsType pass
forall pass.
XKindSig pass -> LHsType pass -> LHsType pass -> HsType pass
HsKindSig NoExtField
XKindSig pass
noExtField LHsKind pass
tvar LHsKind pass
lkind
      where
        tvar :: LHsKind pass
tvar = SrcSpan -> HsType pass -> LHsKind pass
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (XTyVar pass
-> PromotionFlag -> GenLocated SrcSpan (IdP pass) -> HsType pass
forall pass.
XTyVar pass -> PromotionFlag -> Located (IdP pass) -> HsType pass
HsTyVar NoExtField
XTyVar pass
noExtField PromotionFlag
NotPromoted (SrcSpan -> IdP pass -> GenLocated SrcSpan (IdP pass)
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc IdP pass
name))
    mkType (UserTyVar XUserTyVar pass
_ GenLocated SrcSpan (IdP pass)
name) = XTyVar pass
-> PromotionFlag -> GenLocated SrcSpan (IdP pass) -> HsType pass
forall pass.
XTyVar pass -> PromotionFlag -> Located (IdP pass) -> HsType pass
HsTyVar NoExtField
XTyVar pass
noExtField PromotionFlag
NotPromoted GenLocated SrcSpan (IdP pass)
name
    mkType (XTyVarBndr XXTyVarBndr pass
nec) = NoExtCon -> HsType pass
forall a. NoExtCon -> a
noExtCon NoExtCon
XXTyVarBndr pass
nec
mkPseudoFamilyDecl (XFamilyDecl XXFamilyDecl (GhcPass p)
nec) = NoExtCon -> PseudoFamilyDecl (GhcPass p)
forall a. NoExtCon -> a
noExtCon NoExtCon
XXFamilyDecl (GhcPass p)
nec


-- | An instance head that may have documentation and a source location.
type DocInstance name = (InstHead name, Maybe (MDoc (IdP name)), Located (IdP name), Maybe Module)

-- | The head of an instance. Consists of a class name, a list of type
-- parameters (which may be annotated with kinds), and an instance type
data InstHead name = InstHead
    { InstHead name -> IdP name
ihdClsName :: IdP name
    , InstHead name -> [HsType name]
ihdTypes :: [HsType name]
    , InstHead name -> InstType name
ihdInstType :: InstType name
    }


-- | An instance origin information.
--
-- This is used primarily in HTML backend to generate unique instance
-- identifiers (for expandable sections).
data InstOrigin name
    = OriginClass name
    | OriginData name
    | OriginFamily name


instance NamedThing name => NamedThing (InstOrigin name) where

    getName :: InstOrigin name -> Name
getName (OriginClass name
name) = name -> Name
forall a. NamedThing a => a -> Name
getName name
name
    getName (OriginData name
name) = name -> Name
forall a. NamedThing a => a -> Name
getName name
name
    getName (OriginFamily name
name) = name -> Name
forall a. NamedThing a => a -> Name
getName name
name


-----------------------------------------------------------------------------
-- * Documentation comments
-----------------------------------------------------------------------------


type LDoc id = Located (Doc id)

type Doc id = DocH (Wrap (ModuleName, OccName)) (Wrap id)
type MDoc id = MetaDoc (Wrap (ModuleName, OccName)) (Wrap id)

type DocMarkup id a = DocMarkupH (Wrap (ModuleName, OccName)) id a

instance (NFData a, NFData mod)
         => NFData (DocH mod a) where
  rnf :: DocH mod a -> ()
rnf DocH mod a
doc = case DocH mod a
doc of
    DocH mod a
DocEmpty                  -> ()
    DocAppend DocH mod a
a DocH mod a
b             -> DocH mod a
a DocH mod a -> DocH mod a -> DocH mod a
forall a b. NFData a => a -> b -> b
`deepseq` DocH mod a
b DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocString FilePath
a               -> FilePath
a FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocParagraph DocH mod a
a            -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocIdentifier a
a           -> a
a a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocIdentifierUnchecked mod
a  -> mod
a mod -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocModule ModLink (DocH mod a)
a               -> ModLink (DocH mod a)
a ModLink (DocH mod a) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocWarning DocH mod a
a              -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocEmphasis DocH mod a
a             -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocBold DocH mod a
a                 -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocMonospaced DocH mod a
a           -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocUnorderedList [DocH mod a]
a        -> [DocH mod a]
a [DocH mod a] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocOrderedList [DocH mod a]
a          -> [DocH mod a]
a [DocH mod a] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocDefList [(DocH mod a, DocH mod a)]
a              -> [(DocH mod a, DocH mod a)]
a [(DocH mod a, DocH mod a)] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocCodeBlock DocH mod a
a            -> DocH mod a
a DocH mod a -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocHyperlink Hyperlink (DocH mod a)
a            -> Hyperlink (DocH mod a)
a Hyperlink (DocH mod a) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocPic Picture
a                  -> Picture
a Picture -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocMathInline FilePath
a           -> FilePath
a FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocMathDisplay FilePath
a          -> FilePath
a FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocAName FilePath
a                -> FilePath
a FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocProperty FilePath
a             -> FilePath
a FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocExamples [Example]
a             -> [Example]
a [Example] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocHeader Header (DocH mod a)
a               -> Header (DocH mod a)
a Header (DocH mod a) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()
    DocTable Table (DocH mod a)
a                -> Table (DocH mod a)
a Table (DocH mod a) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

#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 ()
instance NFData ModuleName where rnf x = seq x ()
#endif

instance NFData id => NFData (Header id) where
  rnf :: Header id -> ()
rnf (Header Int
a id
b) = Int
a Int -> id -> id
forall a b. NFData a => a -> b -> b
`deepseq` id
b id -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData id => NFData (Hyperlink id) where
  rnf :: Hyperlink id -> ()
rnf (Hyperlink FilePath
a Maybe id
b) = FilePath
a FilePath -> Maybe id -> Maybe id
forall a b. NFData a => a -> b -> b
`deepseq` Maybe id
b Maybe id -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData id => NFData (ModLink id) where
  rnf :: ModLink id -> ()
rnf (ModLink FilePath
a Maybe id
b) = FilePath
a FilePath -> Maybe id -> Maybe id
forall a b. NFData a => a -> b -> b
`deepseq` Maybe id
b Maybe id -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData Picture where
  rnf :: Picture -> ()
rnf (Picture FilePath
a Maybe FilePath
b) = FilePath
a FilePath -> Maybe FilePath -> Maybe FilePath
forall a b. NFData a => a -> b -> b
`deepseq` Maybe FilePath
b Maybe FilePath -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData Example where
  rnf :: Example -> ()
rnf (Example FilePath
a [FilePath]
b) = FilePath
a FilePath -> [FilePath] -> [FilePath]
forall a b. NFData a => a -> b -> b
`deepseq` [FilePath]
b [FilePath] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData id => NFData (Table id) where
    rnf :: Table id -> ()
rnf (Table [TableRow id]
h [TableRow id]
b) = [TableRow id]
h [TableRow id] -> [TableRow id] -> [TableRow id]
forall a b. NFData a => a -> b -> b
`deepseq` [TableRow id]
b [TableRow id] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData id => NFData (TableRow id) where
    rnf :: TableRow id -> ()
rnf (TableRow [TableCell id]
cs) = [TableCell id]
cs [TableCell id] -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

instance NFData id => NFData (TableCell id) where
    rnf :: TableCell id -> ()
rnf (TableCell Int
i Int
j id
c) = Int
i Int -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq` Int
j Int -> id -> id
forall a b. NFData a => a -> b -> b
`deepseq` id
c id -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq` ()

exampleToString :: Example -> String
exampleToString :: Example -> FilePath
exampleToString (Example FilePath
expression [FilePath]
result) =
    FilePath
">>> " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
expression FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"\n" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++  [FilePath] -> FilePath
unlines [FilePath]
result

data HaddockModInfo name = HaddockModInfo
  { HaddockModInfo name -> Maybe (Doc name)
hmi_description :: Maybe (Doc name)
  , HaddockModInfo name -> Maybe FilePath
hmi_copyright   :: Maybe String
  , HaddockModInfo name -> Maybe FilePath
hmi_license     :: Maybe String
  , HaddockModInfo name -> Maybe FilePath
hmi_maintainer  :: Maybe String
  , HaddockModInfo name -> Maybe FilePath
hmi_stability   :: Maybe String
  , HaddockModInfo name -> Maybe FilePath
hmi_portability :: Maybe String
  , HaddockModInfo name -> Maybe FilePath
hmi_safety      :: Maybe String
  , HaddockModInfo name -> Maybe Language
hmi_language    :: Maybe Language
  , HaddockModInfo name -> [Extension]
hmi_extensions  :: [LangExt.Extension]
  }


emptyHaddockModInfo :: HaddockModInfo a
emptyHaddockModInfo :: HaddockModInfo a
emptyHaddockModInfo = HaddockModInfo :: forall name.
Maybe (Doc name)
-> Maybe FilePath
-> Maybe FilePath
-> Maybe FilePath
-> Maybe FilePath
-> Maybe FilePath
-> Maybe FilePath
-> Maybe Language
-> [Extension]
-> HaddockModInfo name
HaddockModInfo
  { hmi_description :: Maybe (Doc a)
hmi_description = Maybe (Doc a)
forall a. Maybe a
Nothing
  , hmi_copyright :: Maybe FilePath
hmi_copyright   = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_license :: Maybe FilePath
hmi_license     = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_maintainer :: Maybe FilePath
hmi_maintainer  = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_stability :: Maybe FilePath
hmi_stability   = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_portability :: Maybe FilePath
hmi_portability = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_safety :: Maybe FilePath
hmi_safety      = Maybe FilePath
forall a. Maybe a
Nothing
  , hmi_language :: Maybe Language
hmi_language    = Maybe Language
forall a. Maybe a
Nothing
  , hmi_extensions :: [Extension]
hmi_extensions  = []
  }


-----------------------------------------------------------------------------
-- * Options
-----------------------------------------------------------------------------


-- | Source-level options for controlling the documentation.
data DocOption
  = OptHide            -- ^ This module should not appear in the docs.
  | OptPrune
  | OptIgnoreExports   -- ^ Pretend everything is exported.
  | OptNotHome         -- ^ Not the best place to get docs for things
                       -- exported by this module.
  | OptShowExtensions  -- ^ Render enabled extensions for this module.
  deriving (DocOption -> DocOption -> Bool
(DocOption -> DocOption -> Bool)
-> (DocOption -> DocOption -> Bool) -> Eq DocOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocOption -> DocOption -> Bool
$c/= :: DocOption -> DocOption -> Bool
== :: DocOption -> DocOption -> Bool
$c== :: DocOption -> DocOption -> Bool
Eq, Int -> DocOption -> ShowS
[DocOption] -> ShowS
DocOption -> FilePath
(Int -> DocOption -> ShowS)
-> (DocOption -> FilePath)
-> ([DocOption] -> ShowS)
-> Show DocOption
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DocOption] -> ShowS
$cshowList :: [DocOption] -> ShowS
show :: DocOption -> FilePath
$cshow :: DocOption -> FilePath
showsPrec :: Int -> DocOption -> ShowS
$cshowsPrec :: Int -> DocOption -> ShowS
Show)


-- | Option controlling how to qualify names
data QualOption
  = OptNoQual         -- ^ Never qualify any names.
  | OptFullQual       -- ^ Qualify all names fully.
  | OptLocalQual      -- ^ Qualify all imported names fully.
  | OptRelativeQual   -- ^ Like local, but strip module prefix
                      --   from modules in the same hierarchy.
  | OptAliasedQual    -- ^ Uses aliases of module names
                      --   as suggested by module import renamings.
                      --   However, we are unfortunately not able
                      --   to maintain the original qualifications.
                      --   Image a re-export of a whole module,
                      --   how could the re-exported identifiers be qualified?

type AliasMap = Map Module ModuleName

data Qualification
  = NoQual
  | FullQual
  | LocalQual Module
  | RelativeQual Module
  | AliasedQual AliasMap Module
       -- ^ @Module@ contains the current module.
       --   This way we can distinguish imported and local identifiers.

makeContentsQual :: QualOption -> Qualification
makeContentsQual :: QualOption -> Qualification
makeContentsQual QualOption
qual =
  case QualOption
qual of
    QualOption
OptNoQual -> Qualification
NoQual
    QualOption
_         -> Qualification
FullQual

makeModuleQual :: QualOption -> AliasMap -> Module -> Qualification
makeModuleQual :: QualOption -> AliasMap -> Module -> Qualification
makeModuleQual QualOption
qual AliasMap
aliases Module
mdl =
  case QualOption
qual of
    QualOption
OptLocalQual      -> Module -> Qualification
LocalQual Module
mdl
    QualOption
OptRelativeQual   -> Module -> Qualification
RelativeQual Module
mdl
    QualOption
OptAliasedQual    -> AliasMap -> Module -> Qualification
AliasedQual AliasMap
aliases Module
mdl
    QualOption
OptFullQual       -> Qualification
FullQual
    QualOption
OptNoQual         -> Qualification
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

-- | When to qualify @since@ annotations with their package
data SinceQual
  = Always
  | External -- ^ only qualify when the thing being annotated is from
             -- an external package

-----------------------------------------------------------------------------
-- * Error handling
-----------------------------------------------------------------------------


-- A monad which collects error messages, locally defined to avoid a dep on mtl


type ErrMsg = String
newtype ErrMsgM a = Writer { ErrMsgM a -> (a, [FilePath])
runWriter :: (a, [ErrMsg]) }


instance Functor ErrMsgM where
        fmap :: (a -> b) -> ErrMsgM a -> ErrMsgM b
fmap a -> b
f (Writer (a
a, [FilePath]
msgs)) = (b, [FilePath]) -> ErrMsgM b
forall a. (a, [FilePath]) -> ErrMsgM a
Writer (a -> b
f a
a, [FilePath]
msgs)

instance Applicative ErrMsgM where
    pure :: a -> ErrMsgM a
pure a
a = (a, [FilePath]) -> ErrMsgM a
forall a. (a, [FilePath]) -> ErrMsgM a
Writer (a
a, [])
    <*> :: ErrMsgM (a -> b) -> ErrMsgM a -> ErrMsgM b
(<*>)  = ErrMsgM (a -> b) -> ErrMsgM a -> ErrMsgM b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap

instance Monad ErrMsgM where
        return :: a -> ErrMsgM a
return   = a -> ErrMsgM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
        ErrMsgM a
m >>= :: ErrMsgM a -> (a -> ErrMsgM b) -> ErrMsgM b
>>= a -> ErrMsgM b
k  = (b, [FilePath]) -> ErrMsgM b
forall a. (a, [FilePath]) -> ErrMsgM a
Writer ((b, [FilePath]) -> ErrMsgM b) -> (b, [FilePath]) -> ErrMsgM b
forall a b. (a -> b) -> a -> b
$ let
                (a
a, [FilePath]
w)  = ErrMsgM a -> (a, [FilePath])
forall a. ErrMsgM a -> (a, [FilePath])
runWriter ErrMsgM a
m
                (b
b, [FilePath]
w') = ErrMsgM b -> (b, [FilePath])
forall a. ErrMsgM a -> (a, [FilePath])
runWriter (a -> ErrMsgM b
k a
a)
                in (b
b, [FilePath]
w [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath]
w')


tell :: [ErrMsg] -> ErrMsgM ()
tell :: [FilePath] -> ErrMsgM ()
tell [FilePath]
w = ((), [FilePath]) -> ErrMsgM ()
forall a. (a, [FilePath]) -> ErrMsgM a
Writer ((), [FilePath]
w)


-- Exceptions


-- | Haddock's own exception type.
data HaddockException
  = HaddockException String
  | WithContext [String] SomeException
  deriving Typeable


instance Show HaddockException where
  show :: HaddockException -> FilePath
show (HaddockException FilePath
str) = FilePath
str
  show (WithContext [FilePath]
ctxts SomeException
se)  = [FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath
"While " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
ctxt FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
":\n" | FilePath
ctxt <- [FilePath] -> [FilePath]
forall a. [a] -> [a]
reverse [FilePath]
ctxts] [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [SomeException -> FilePath
forall a. Show a => a -> FilePath
show SomeException
se]

throwE :: String -> a
instance Exception HaddockException
throwE :: FilePath -> a
throwE FilePath
str = HaddockException -> a
forall a e. Exception e => e -> a
throw (FilePath -> HaddockException
HaddockException FilePath
str)

withExceptionContext :: ExceptionMonad m => String -> m a -> m a
withExceptionContext :: FilePath -> m a -> m a
withExceptionContext FilePath
ctxt =
  (HaddockException -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
(e -> m a) -> m a -> m a
ghandle (\HaddockException
ex ->
      case HaddockException
ex of
        HaddockException FilePath
_ -> HaddockException -> m a
forall a e. Exception e => e -> a
throw (HaddockException -> m a) -> HaddockException -> m a
forall a b. (a -> b) -> a -> b
$ [FilePath] -> SomeException -> HaddockException
WithContext [FilePath
ctxt] (HaddockException -> SomeException
forall e. Exception e => e -> SomeException
toException HaddockException
ex)
        WithContext [FilePath]
ctxts SomeException
se -> HaddockException -> m a
forall a e. Exception e => e -> a
throw (HaddockException -> m a) -> HaddockException -> m a
forall a b. (a -> b) -> a -> b
$ [FilePath] -> SomeException -> HaddockException
WithContext (FilePath
ctxtFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
ctxts) SomeException
se
          ) (m a -> m a) -> (m a -> m a) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (SomeException -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
(e -> m a) -> m a -> m a
ghandle (HaddockException -> m a
forall a e. Exception e => e -> a
throw (HaddockException -> m a)
-> (SomeException -> HaddockException) -> SomeException -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> SomeException -> HaddockException
WithContext [FilePath
ctxt])

-- In "Haddock.Interface.Create", we need to gather
-- @Haddock.Types.ErrMsg@s a lot, like @ErrMsgM@ does,
-- but we can't just use @GhcT ErrMsgM@ because GhcT requires the
-- transformed monad to be MonadIO.
newtype ErrMsgGhc a = WriterGhc { ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc :: Ghc (a, [ErrMsg]) }
--instance MonadIO ErrMsgGhc where
--  liftIO = WriterGhc . fmap (\a->(a,[])) liftIO
--er, implementing GhcMonad involves annoying ExceptionMonad and
--WarnLogMonad classes, so don't bother.
liftGhcToErrMsgGhc :: Ghc a -> ErrMsgGhc a
liftGhcToErrMsgGhc :: Ghc a -> ErrMsgGhc a
liftGhcToErrMsgGhc = Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (a, [FilePath]) -> ErrMsgGhc a)
-> (Ghc a -> Ghc (a, [FilePath])) -> Ghc a -> ErrMsgGhc a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (a, [FilePath])) -> Ghc a -> Ghc (a, [FilePath])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
a->(a
a,[]))
liftErrMsg :: ErrMsgM a -> ErrMsgGhc a
liftErrMsg :: ErrMsgM a -> ErrMsgGhc a
liftErrMsg = Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (a, [FilePath]) -> ErrMsgGhc a)
-> (ErrMsgM a -> Ghc (a, [FilePath])) -> ErrMsgM a -> ErrMsgGhc a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, [FilePath]) -> Ghc (a, [FilePath])
forall (m :: * -> *) a. Monad m => a -> m a
return ((a, [FilePath]) -> Ghc (a, [FilePath]))
-> (ErrMsgM a -> (a, [FilePath]))
-> ErrMsgM a
-> Ghc (a, [FilePath])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrMsgM a -> (a, [FilePath])
forall a. ErrMsgM a -> (a, [FilePath])
runWriter
--  for now, use (liftErrMsg . tell) for this
--tell :: [ErrMsg] -> ErrMsgGhc ()
--tell msgs = WriterGhc $ return ( (), msgs )


instance Functor ErrMsgGhc where
  fmap :: (a -> b) -> ErrMsgGhc a -> ErrMsgGhc b
fmap a -> b
f (WriterGhc Ghc (a, [FilePath])
x) = Ghc (b, [FilePath]) -> ErrMsgGhc b
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (((a, [FilePath]) -> (b, [FilePath]))
-> Ghc (a, [FilePath]) -> Ghc (b, [FilePath])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> (a, [FilePath]) -> (b, [FilePath])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first a -> b
f) Ghc (a, [FilePath])
x)

instance Applicative ErrMsgGhc where
    pure :: a -> ErrMsgGhc a
pure a
a = Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc ((a, [FilePath]) -> Ghc (a, [FilePath])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, []))
    <*> :: ErrMsgGhc (a -> b) -> ErrMsgGhc a -> ErrMsgGhc b
(<*>) = ErrMsgGhc (a -> b) -> ErrMsgGhc a -> ErrMsgGhc b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap

instance Monad ErrMsgGhc where
  return :: a -> ErrMsgGhc a
return = a -> ErrMsgGhc a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
  ErrMsgGhc a
m >>= :: ErrMsgGhc a -> (a -> ErrMsgGhc b) -> ErrMsgGhc b
>>= a -> ErrMsgGhc b
k = Ghc (b, [FilePath]) -> ErrMsgGhc b
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (b, [FilePath]) -> ErrMsgGhc b)
-> Ghc (b, [FilePath]) -> ErrMsgGhc b
forall a b. (a -> b) -> a -> b
$ ErrMsgGhc a -> Ghc (a, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc ErrMsgGhc a
m Ghc (a, [FilePath])
-> ((a, [FilePath]) -> Ghc (b, [FilePath])) -> Ghc (b, [FilePath])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ (a
a, [FilePath]
msgs1) ->
               ((b, [FilePath]) -> (b, [FilePath]))
-> Ghc (b, [FilePath]) -> Ghc (b, [FilePath])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([FilePath] -> [FilePath]) -> (b, [FilePath]) -> (b, [FilePath])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ([FilePath]
msgs1 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++)) (ErrMsgGhc b -> Ghc (b, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc (a -> ErrMsgGhc b
k a
a))

instance MonadIO ErrMsgGhc where
  liftIO :: IO a -> ErrMsgGhc a
liftIO IO a
m = Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc ((a -> (a, [FilePath])) -> Ghc a -> Ghc (a, [FilePath])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
x -> (a
x, [])) (IO a -> Ghc a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
m))

instance ExceptionMonad ErrMsgGhc where
  gcatch :: ErrMsgGhc a -> (e -> ErrMsgGhc a) -> ErrMsgGhc a
gcatch ErrMsgGhc a
act e -> ErrMsgGhc a
hand = Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (a, [FilePath]) -> ErrMsgGhc a)
-> Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a b. (a -> b) -> a -> b
$
    ErrMsgGhc a -> Ghc (a, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc ErrMsgGhc a
act Ghc (a, [FilePath])
-> (e -> Ghc (a, [FilePath])) -> Ghc (a, [FilePath])
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
`gcatch` (ErrMsgGhc a -> Ghc (a, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc (ErrMsgGhc a -> Ghc (a, [FilePath]))
-> (e -> ErrMsgGhc a) -> e -> Ghc (a, [FilePath])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ErrMsgGhc a
hand)
  gmask :: ((ErrMsgGhc a -> ErrMsgGhc a) -> ErrMsgGhc b) -> ErrMsgGhc b
gmask (ErrMsgGhc a -> ErrMsgGhc a) -> ErrMsgGhc b
act = Ghc (b, [FilePath]) -> ErrMsgGhc b
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (b, [FilePath]) -> ErrMsgGhc b)
-> Ghc (b, [FilePath]) -> ErrMsgGhc b
forall a b. (a -> b) -> a -> b
$ ((Ghc (a, [FilePath]) -> Ghc (a, [FilePath]))
 -> Ghc (b, [FilePath]))
-> Ghc (b, [FilePath])
forall (m :: * -> *) a b.
ExceptionMonad m =>
((m a -> m a) -> m b) -> m b
gmask (((Ghc (a, [FilePath]) -> Ghc (a, [FilePath]))
  -> Ghc (b, [FilePath]))
 -> Ghc (b, [FilePath]))
-> ((Ghc (a, [FilePath]) -> Ghc (a, [FilePath]))
    -> Ghc (b, [FilePath]))
-> Ghc (b, [FilePath])
forall a b. (a -> b) -> a -> b
$ \Ghc (a, [FilePath]) -> Ghc (a, [FilePath])
mask' ->
    ErrMsgGhc b -> Ghc (b, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc (ErrMsgGhc b -> Ghc (b, [FilePath]))
-> ErrMsgGhc b -> Ghc (b, [FilePath])
forall a b. (a -> b) -> a -> b
$ (ErrMsgGhc a -> ErrMsgGhc a) -> ErrMsgGhc b
act (Ghc (a, [FilePath]) -> ErrMsgGhc a
forall a. Ghc (a, [FilePath]) -> ErrMsgGhc a
WriterGhc (Ghc (a, [FilePath]) -> ErrMsgGhc a)
-> (ErrMsgGhc a -> Ghc (a, [FilePath]))
-> ErrMsgGhc a
-> ErrMsgGhc a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ghc (a, [FilePath]) -> Ghc (a, [FilePath])
mask'  (Ghc (a, [FilePath]) -> Ghc (a, [FilePath]))
-> (ErrMsgGhc a -> Ghc (a, [FilePath]))
-> ErrMsgGhc a
-> Ghc (a, [FilePath])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrMsgGhc a -> Ghc (a, [FilePath])
forall a. ErrMsgGhc a -> Ghc (a, [FilePath])
runWriterGhc)

-----------------------------------------------------------------------------
-- * Pass sensitive types
-----------------------------------------------------------------------------

type instance XRec DocNameI f = Located (f DocNameI)

type instance XForAllTy        DocNameI = NoExtField
type instance XQualTy          DocNameI = NoExtField
type instance XTyVar           DocNameI = NoExtField
type instance XStarTy          DocNameI = NoExtField
type instance XAppTy           DocNameI = NoExtField
type instance XAppKindTy       DocNameI = NoExtField
type instance XFunTy           DocNameI = NoExtField
type instance XListTy          DocNameI = NoExtField
type instance XTupleTy         DocNameI = NoExtField
type instance XSumTy           DocNameI = NoExtField
type instance XOpTy            DocNameI = NoExtField
type instance XParTy           DocNameI = NoExtField
type instance XIParamTy        DocNameI = NoExtField
type instance XKindSig         DocNameI = NoExtField
type instance XSpliceTy        DocNameI = Void       -- see `renameHsSpliceTy`
type instance XDocTy           DocNameI = NoExtField
type instance XBangTy          DocNameI = NoExtField
type instance XRecTy           DocNameI = NoExtField
type instance XExplicitListTy  DocNameI = NoExtField
type instance XExplicitTupleTy DocNameI = NoExtField
type instance XTyLit           DocNameI = NoExtField
type instance XWildCardTy      DocNameI = NoExtField
type instance XXType           DocNameI = NewHsTypeX

type instance XUserTyVar    DocNameI = NoExtField
type instance XKindedTyVar  DocNameI = NoExtField
type instance XXTyVarBndr   DocNameI = NoExtCon

type instance XCFieldOcc   DocNameI = DocName
type instance XXFieldOcc   DocNameI = NoExtField

type instance XFixitySig   DocNameI = NoExtField
type instance XFixSig      DocNameI = NoExtField
type instance XPatSynSig   DocNameI = NoExtField
type instance XClassOpSig  DocNameI = NoExtField
type instance XTypeSig     DocNameI = NoExtField
type instance XMinimalSig  DocNameI = NoExtField

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 XDerivD     DocNameI = NoExtField
type instance XInstD      DocNameI = NoExtField
type instance XForD       DocNameI = NoExtField
type instance XSigD       DocNameI = NoExtField
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 XCFamEqn       DocNameI _ = NoExtField
type instance XXFamEqn       DocNameI _ = NoExtCon

type instance XCClsInstDecl DocNameI = NoExtField
type instance XCDerivDecl   DocNameI = NoExtField
type instance XViaStrategy  DocNameI = LHsSigType DocNameI
type instance XDataFamInstD DocNameI = NoExtField
type instance XTyFamInstD   DocNameI = NoExtField
type instance XClsInstD     DocNameI = NoExtField
type instance XCHsDataDefn  DocNameI = NoExtField
type instance XCFamilyDecl  DocNameI = NoExtField
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 XHsIB             DocNameI _ = NoExtField
type instance XHsWC             DocNameI _ = NoExtField
type instance XXHsImplicitBndrs DocNameI _ = NoExtCon

type instance XHsQTvs        DocNameI = NoExtField
type instance XConDeclField  DocNameI = NoExtField
type instance XXConDeclField DocNameI = NoExtCon

type instance XXPat DocNameI = NoExtCon