aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Haddock/Types.hs')
-rw-r--r--src/Haddock/Types.hs33
1 files changed, 13 insertions, 20 deletions
diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs
index 73fafd6b..00a8b68f 100644
--- a/src/Haddock/Types.hs
+++ b/src/Haddock/Types.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
+{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, GADTs #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-----------------------------------------------------------------------------
-- |
@@ -19,7 +19,6 @@ module Haddock.Types (
, HsDocString, LHsDocString
) where
-
import Data.Foldable
import Data.Traversable
import Control.Exception
@@ -27,15 +26,12 @@ import Control.Arrow
import Control.DeepSeq
import Data.Typeable
import Data.Map (Map)
-import Data.Maybe
import qualified Data.Map as Map
-import Data.Monoid
import GHC hiding (NoLink)
import OccName
import Control.Applicative (Applicative(..))
import Control.Monad (ap)
-
-----------------------------------------------------------------------------
-- * Convenient synonyms
-----------------------------------------------------------------------------
@@ -205,7 +201,7 @@ data ExportItem name
, expItemSubs :: ![name]
}
- -- | A section heading.
+ -- | A section heading.
| ExportGroup
{
-- | Section level (1, 2, 3, ...).
@@ -230,11 +226,6 @@ data Documentation name = Documentation
} deriving Functor
-combineDocumentation :: Documentation name -> Maybe (Doc name)
-combineDocumentation (Documentation Nothing Nothing) = Nothing
-combineDocumentation (Documentation mDoc mWarning) = Just (fromMaybe mempty mWarning `mappend` fromMaybe mempty mDoc)
-
-
-- | 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 (Doc name)
@@ -289,7 +280,6 @@ type DocInstance name = (InstHead name, Maybe (Doc name))
-- of instance types.
type InstHead name = ([HsType name], name, [HsType name])
-
-----------------------------------------------------------------------------
-- * Documentation comments
-----------------------------------------------------------------------------
@@ -314,18 +304,12 @@ data Doc id
| DocDefList [(Doc id, Doc id)]
| DocCodeBlock (Doc id)
| DocHyperlink Hyperlink
- | DocPic String
+ | DocPic Picture
| DocAName String
| DocProperty String
| DocExamples [Example]
deriving (Functor, Foldable, Traversable)
-
-instance Monoid (Doc id) where
- mempty = DocEmpty
- mappend = DocAppend
-
-
instance NFData a => NFData (Doc a) where
rnf doc = case doc of
DocEmpty -> ()
@@ -360,9 +344,18 @@ data Hyperlink = Hyperlink
} deriving (Eq, Show)
+data Picture = Picture
+ { pictureUri :: String
+ , pictureTitle :: Maybe String
+ } deriving (Eq, Show)
+
+
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
@@ -396,7 +389,7 @@ data DocMarkup id a = Markup
, markupCodeBlock :: a -> a
, markupHyperlink :: Hyperlink -> a
, markupAName :: String -> a
- , markupPic :: String -> a
+ , markupPic :: Picture -> a
, markupProperty :: String -> a
, markupExample :: [Example] -> a
}