module Haddock.Types (
  module Haddock.Types
  , HsDocString, LHsDocString
  , Fixity(..)
 ) where
import Data.Foldable
import Data.Traversable
import Control.Exception
import Control.Arrow hiding ((<+>))
import Control.DeepSeq
import Data.Typeable
import Data.Map (Map)
import qualified Data.Map as Map
import BasicTypes (Fixity(..))
import GHC hiding (NoLink)
import DynFlags (ExtensionFlag, Language)
import OccName
import Outputable
import Control.Applicative (Applicative(..))
import Control.Monad (ap)
type IfaceMap      = Map Module Interface
type InstIfaceMap  = Map Module InstalledInterface  
type DocMap a      = Map Name (Doc a)
type ArgMap a      = Map Name (Map Int (Doc a))
type SubMap        = Map Name [Name]
type DeclMap       = Map Name [LHsDecl Name]
type InstMap       = Map SrcSpan Name
type FixMap        = Map Name Fixity
type SrcMap        = Map PackageId FilePath
type DocPaths      = (FilePath, Maybe FilePath) 
data Interface = Interface
  {
    
    ifaceMod             :: !Module
    
  , ifaceOrigFilename    :: !FilePath
    
  , ifaceInfo            :: !(HaddockModInfo Name)
    
  , ifaceDoc             :: !(Documentation Name)
    
  , ifaceRnDoc           :: !(Documentation DocName)
    
  , ifaceOptions         :: ![DocOption]
    
    
    
  , ifaceDeclMap         :: !(Map Name [LHsDecl Name])
    
    
  , ifaceDocMap          :: !(DocMap Name)
  , ifaceArgMap          :: !(ArgMap Name)
    
    
  , ifaceRnDocMap        :: !(DocMap DocName)
  , ifaceRnArgMap        :: !(ArgMap DocName)
  , ifaceSubMap          :: !(Map Name [Name])
  , ifaceFixMap          :: !(Map Name Fixity)
  , ifaceExportItems     :: ![ExportItem Name]
  , ifaceRnExportItems   :: ![ExportItem DocName]
    
  , ifaceExports         :: ![Name]
    
    
    
  , ifaceVisibleExports  :: ![Name]
    
  , ifaceModuleAliases   :: !AliasMap
    
  , ifaceInstances       :: ![ClsInst]
  , ifaceFamInstances    :: ![FamInst]
    
    
  , ifaceHaddockCoverage :: !(Int, Int)
    
  , ifaceWarningMap :: !WarningMap
  }
type WarningMap = DocMap Name
data InstalledInterface = InstalledInterface
  {
    
    instMod            :: Module
    
  , instInfo           :: HaddockModInfo Name
    
    
  , instDocMap         :: DocMap Name
  , instArgMap         :: ArgMap Name
    
  , instExports        :: [Name]
    
    
    
  , instVisibleExports :: [Name]
    
  , instOptions        :: [DocOption]
  , instSubMap         :: Map Name [Name]
  , instFixMap         :: Map Name Fixity
  }
toInstalledIface :: Interface -> InstalledInterface
toInstalledIface interface = InstalledInterface
  { instMod            = ifaceMod            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
  }
data ExportItem name
  
  = ExportDecl
      {
        
        expItemDecl :: !(LHsDecl name)
        
        
      , expItemMbDoc :: !(DocForDecl name)
        
      , expItemSubDocs :: ![(name, DocForDecl name)]
        
        
      , expItemInstances :: ![DocInstance name]
        
      , expItemFixities :: ![(name, Fixity)]
        
        
      , expItemSpliced :: !Bool
      }
  
  
  | ExportNoDecl
      { expItemName :: !name
        
      , expItemSubs :: ![name]
      }
  
  | ExportGroup
      {
        
        expItemSectionLevel :: !Int
        
      , expItemSectionId :: !String
        
      , expItemSectionText :: !(Doc name)
      }
  
  | ExportDoc !(Doc name)
  
  | ExportModule !Module
data Documentation name = Documentation
  { documentationDoc :: Maybe (Doc name)
  , documentationWarning :: !(Maybe (Doc name))
  } deriving Functor
type FnArgsDoc name = Map Int (Doc name)
type DocForDecl name = (Documentation name, FnArgsDoc name)
noDocForDecl :: DocForDecl name
noDocForDecl = (Documentation Nothing Nothing, Map.empty)
unrenameDocForDecl :: DocForDecl DocName -> DocForDecl Name
unrenameDocForDecl (doc, fnArgsDoc) =
    (fmap getName doc, (fmap . fmap) getName fnArgsDoc)
type LinkEnv = Map Name Module
data DocName
  = Documented Name Module
     
     
     
  | Undocumented Name
     
     
  deriving Eq
instance NamedThing DocName where
  getName (Documented name _) = name
  getName (Undocumented name) = name
data InstType name
  = ClassInst [HsType name]         
  | TypeInst  (Maybe (HsType name)) 
  | DataInst (TyClDecl name)        
instance OutputableBndr a => Outputable (InstType a) where
  ppr (ClassInst a) = text "ClassInst" <+> ppr a
  ppr (TypeInst  a) = text "TypeInst"  <+> ppr a
  ppr (DataInst  a) = text "DataInst"  <+> ppr a
type DocInstance name = (InstHead name, Maybe (Doc name))
type InstHead name = (name, [HsType name], [HsType name], InstType name)
type LDoc id = Located (Doc id)
data Doc id
  = DocEmpty
  | DocAppend (Doc id) (Doc id)
  | DocString String
  | DocParagraph (Doc id)
  | DocIdentifier id
  | DocIdentifierUnchecked (ModuleName, OccName)
  | DocModule String
  | DocWarning (Doc id)
  | DocEmphasis (Doc id)
  | DocMonospaced (Doc id)
  | DocBold (Doc id)
  | DocUnorderedList [Doc id]
  | DocOrderedList [Doc id]
  | DocDefList [(Doc id, Doc id)]
  | DocCodeBlock (Doc id)
  | DocHyperlink Hyperlink
  | DocPic Picture
  | DocAName String
  | DocProperty String
  | DocExamples [Example]
  | DocHeader (Header (Doc id))
  deriving (Functor, Foldable, Traversable)
instance Foldable Header where
  foldMap f (Header _ a) = f a
instance Traversable Header where
  traverse f (Header l a) = Header l `fmap` f a
instance NFData a => NFData (Doc a) where
  rnf doc = case doc of
    DocEmpty                  -> ()
    DocAppend a b             -> a `deepseq` b `deepseq` ()
    DocString a               -> a `deepseq` ()
    DocParagraph a            -> a `deepseq` ()
    DocIdentifier a           -> a `deepseq` ()
    DocIdentifierUnchecked a  -> a `deepseq` ()
    DocModule a               -> a `deepseq` ()
    DocWarning a              -> a `deepseq` ()
    DocEmphasis a             -> a `deepseq` ()
    DocBold a                 -> a `deepseq` ()
    DocMonospaced a           -> a `deepseq` ()
    DocUnorderedList a        -> a `deepseq` ()
    DocOrderedList a          -> a `deepseq` ()
    DocDefList a              -> a `deepseq` ()
    DocCodeBlock a            -> a `deepseq` ()
    DocHyperlink a            -> a `deepseq` ()
    DocPic a                  -> a `deepseq` ()
    DocAName a                -> a `deepseq` ()
    DocProperty a             -> a `deepseq` ()
    DocExamples a             -> a `deepseq` ()
    DocHeader a               -> a `deepseq` ()
instance NFData Name
instance NFData OccName
instance NFData ModuleName
data Hyperlink = Hyperlink
  { hyperlinkUrl   :: String
  , hyperlinkLabel :: Maybe String
  } deriving (Eq, Show)
data Picture = Picture
  { pictureUri   :: String
  , pictureTitle :: Maybe String
  } deriving (Eq, Show)
data Header id = Header
  { headerLevel :: Int
  , headerTitle :: id
  } deriving Functor
instance NFData id => NFData (Header id) where
  rnf (Header a b) = a `deepseq` b `deepseq` ()
instance NFData Hyperlink where
  rnf (Hyperlink a b) = a `deepseq` b `deepseq` ()
instance NFData Picture where
  rnf (Picture a b) = a `deepseq` b `deepseq` ()
data Example = Example
  { exampleExpression :: String
  , exampleResult     :: [String]
  } deriving (Eq, Show)
instance NFData Example where
  rnf (Example a b) = a `deepseq` b `deepseq` ()
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
  , markupProperty             :: String -> a
  , markupExample              :: [Example] -> a
  , markupHeader               :: Header a -> a
  }
data HaddockModInfo name = HaddockModInfo
  { hmi_description :: Maybe (Doc name)
  , hmi_copyright   :: Maybe String
  , hmi_license     :: Maybe String
  , hmi_maintainer  :: Maybe String
  , hmi_stability   :: Maybe String
  , hmi_portability :: Maybe String
  , hmi_safety      :: Maybe String
  , hmi_language    :: Maybe Language
  , hmi_extensions  :: [ExtensionFlag]
  }
emptyHaddockModInfo :: HaddockModInfo a
emptyHaddockModInfo = HaddockModInfo
  { hmi_description = Nothing
  , hmi_copyright   = Nothing
  , hmi_license     = Nothing
  , hmi_maintainer  = Nothing
  , hmi_stability   = Nothing
  , hmi_portability = Nothing
  , hmi_safety      = Nothing
  , hmi_language    = Nothing
  , hmi_extensions  = []
  }
data DocOption
  = OptHide            
  | OptPrune
  | OptIgnoreExports   
  | OptNotHome         
                       
  | OptShowExtensions  
  deriving (Eq, Show)
data QualOption
  = OptNoQual         
  | OptFullQual       
  | OptLocalQual      
  | OptRelativeQual   
                      
  | OptAliasedQual    
                      
                      
                      
                      
                      
type AliasMap = Map Module ModuleName
data Qualification
  = NoQual
  | FullQual
  | LocalQual Module
  | RelativeQual Module
  | AliasedQual AliasMap Module
       
       
makeContentsQual :: QualOption -> Qualification
makeContentsQual qual =
  case qual of
    OptNoQual -> NoQual
    _         -> FullQual
makeModuleQual :: QualOption -> AliasMap -> Module -> Qualification
makeModuleQual qual aliases mdl =
  case qual of
    OptLocalQual      -> LocalQual mdl
    OptRelativeQual   -> RelativeQual mdl
    OptAliasedQual    -> AliasedQual aliases mdl
    OptFullQual       -> FullQual
    OptNoQual         -> NoQual
type ErrMsg = String
newtype ErrMsgM a = Writer { runWriter :: (a, [ErrMsg]) }
instance Functor ErrMsgM where
        fmap f (Writer (a, msgs)) = Writer (f a, msgs)
instance Applicative ErrMsgM where
    pure = return
    (<*>) = ap
instance Monad ErrMsgM where
        return a = Writer (a, [])
        m >>= k  = Writer $ let
                (a, w)  = runWriter m
                (b, w') = runWriter (k a)
                in (b, w ++ w')
tell :: [ErrMsg] -> ErrMsgM ()
tell w = Writer ((), w)
data HaddockException = HaddockException String deriving Typeable
instance Show HaddockException where
  show (HaddockException str) = str
throwE :: String -> a
instance Exception HaddockException
throwE str = throw (HaddockException str)
newtype ErrMsgGhc a = WriterGhc { runWriterGhc :: Ghc (a, [ErrMsg]) }
liftGhcToErrMsgGhc :: Ghc a -> ErrMsgGhc a
liftGhcToErrMsgGhc = WriterGhc . fmap (\a->(a,[]))
liftErrMsg :: ErrMsgM a -> ErrMsgGhc a
liftErrMsg = WriterGhc . return . runWriter
instance Functor ErrMsgGhc where
  fmap f (WriterGhc x) = WriterGhc (fmap (first f) x)
instance Applicative ErrMsgGhc where
    pure = return
    (<*>) = ap
instance Monad ErrMsgGhc where
  return a = WriterGhc (return (a, []))
  m >>= k = WriterGhc $ runWriterGhc m >>= \ (a, msgs1) ->
               fmap (second (msgs1 ++)) (runWriterGhc (k a))