summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Haddock.hs
blob: a3dfb7c3c77f618cd0077305f5410b0ccb0b15a6 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
{- |
   Module      : Text.Pandoc.Readers.Haddock
   Copyright   : Copyright (C) 2013 David Lazar
   License     : GNU GPL, version 2 or above

   Maintainer  : David Lazar <lazar6@illinois.edu>,
                 John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha

Conversion of Haddock markup to 'Pandoc' document.
-}
module Text.Pandoc.Readers.Haddock
    ( readHaddock
    ) where

import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Shared (trim, splitBy)
import Data.Monoid
import Data.List (intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Documentation.Haddock.Parser
import Documentation.Haddock.Types
import Debug.Trace (trace)

-- | Parse Haddock markup and return a 'Pandoc' document.
readHaddock :: ReaderOptions -- ^ Reader options
            -> String        -- ^ String to parse
            -> Pandoc
readHaddock opts = B.doc . docHToBlocks . trace' . parseParas
  where trace' x = if readerTrace opts
                      then trace (show x) x
                      else x

docHToBlocks :: DocH String Identifier -> Blocks
docHToBlocks d' =
  case d' of
    DocEmpty -> mempty
    DocAppend (DocParagraph (DocHeader h)) (DocParagraph (DocAName ident)) ->
         B.headerWith (ident,[],[]) (headerLevel h)
            (docHToInlines False $ headerTitle h)
    DocAppend d1 d2 -> mappend (docHToBlocks d1) (docHToBlocks d2)
    DocString _ -> inlineFallback
    DocParagraph (DocHeader h) -> docHToBlocks (DocHeader h)
    DocParagraph (DocAName h) -> B.plain $ docHToInlines False $ DocAName h
    DocParagraph x -> let (ils, rest) = getInlines x
                       in (B.para $ docHToInlines False ils)
                          <> docHToBlocks rest
    DocIdentifier _ -> inlineFallback
    DocIdentifierUnchecked _ -> inlineFallback
    DocModule s -> B.plain $ docHToInlines False $ DocModule s
    DocWarning _ -> mempty -- TODO
    DocEmphasis _ -> inlineFallback
    DocMonospaced _ -> inlineFallback
    DocBold _ -> inlineFallback
    DocHeader h -> B.header (headerLevel h)
                           (docHToInlines False $ headerTitle h)
    DocUnorderedList items -> B.bulletList (map docHToBlocks items)
    DocOrderedList items -> B.orderedList (map docHToBlocks items)
    DocDefList items -> B.definitionList (map (\(d,t) ->
                               (docHToInlines False d,
                                [consolidatePlains $ docHToBlocks t])) items)
    DocCodeBlock (DocString s) -> B.codeBlockWith ("",[],[]) s
    DocCodeBlock d -> B.para $ docHToInlines True d
    DocHyperlink _ -> inlineFallback
    DocPic _ -> inlineFallback
    DocAName _ -> inlineFallback
    DocProperty s -> B.codeBlockWith ("",["property","haskell"],[]) (trim s)
    DocExamples es -> mconcat $ map (\e ->
       makeExample ">>>" (exampleExpression e) (exampleResult e)) es

  where inlineFallback = B.plain $ docHToInlines False d'
        consolidatePlains = B.fromList . consolidatePlains' . B.toList
        consolidatePlains' zs@(Plain _ : _) =
          let (xs, ys) = span isPlain zs in
          Para (concatMap extractContents xs) : consolidatePlains' ys
        consolidatePlains' (x : xs) = x : consolidatePlains' xs
        consolidatePlains' [] = []
        isPlain (Plain _) = True
        isPlain _         = False
        extractContents (Plain xs) = xs
        extractContents _ = []

docHToInlines :: Bool -> DocH String Identifier -> Inlines
docHToInlines isCode d' =
  case d' of
    DocEmpty -> mempty
    DocAppend d1 d2 -> mappend (docHToInlines isCode d1)
                               (docHToInlines isCode d2)
    DocString s
      | isCode -> mconcat $ intersperse B.linebreak
                              $ map B.code $ splitBy (=='\n') s
      | otherwise  -> B.text s
    DocParagraph _ -> mempty
    DocIdentifier (_,s,_) -> B.codeWith ("",["haskell","identifier"],[]) s
    DocIdentifierUnchecked s -> B.codeWith ("",["haskell","identifier"],[]) s
    DocModule s -> B.codeWith ("",["haskell","module"],[]) s
    DocWarning _ -> mempty -- TODO
    DocEmphasis d -> B.emph (docHToInlines isCode d)
    DocMonospaced (DocString s) -> B.code s
    DocMonospaced d -> docHToInlines True d
    DocBold d -> B.strong (docHToInlines isCode d)
    DocHeader _ -> mempty
    DocUnorderedList _ -> mempty
    DocOrderedList _ -> mempty
    DocDefList _ -> mempty
    DocCodeBlock _ -> mempty
    DocHyperlink h -> B.link (hyperlinkUrl h) (hyperlinkUrl h)
             (maybe (B.text $ hyperlinkUrl h) B.text $ hyperlinkLabel h)
    DocPic p -> B.image (pictureUri p) (fromMaybe (pictureUri p) $ pictureTitle p)
                        (maybe mempty B.text $ pictureTitle p)
    DocAName s -> B.spanWith (s,["anchor"],[]) mempty
    DocProperty _ -> mempty
    DocExamples _ -> mempty

getInlines :: DocH String Identifier -> (DocH String Identifier, DocH String Identifier)
getInlines (DocAppend x y) = if isInline x
                                then let (a, b) = getInlines y
                                     in  (DocAppend x a, b)
                                else (DocEmpty, DocAppend x y)
getInlines x = if isInline x
                  then (x, DocEmpty)
                  else (DocEmpty, x)

isInline :: DocH String Identifier -> Bool
isInline d' =
  case d' of
    DocEmpty -> True
    DocAppend d1 _ -> isInline d1
    DocString _ -> True
    DocParagraph _ -> False
    DocIdentifier _ -> True
    DocIdentifierUnchecked _ -> True
    DocModule _ -> True
    DocWarning _ -> True
    DocEmphasis _ -> True
    DocMonospaced _ -> True
    DocBold _ -> True
    DocHeader _ -> False
    DocUnorderedList _ -> False
    DocOrderedList _ -> False
    DocDefList _ -> False
    DocCodeBlock _ -> False
    DocHyperlink _ -> True
    DocPic _ -> True
    DocAName _ -> True
    DocProperty _ -> False
    DocExamples _ -> False

-- | Create an 'Example', stripping superfluous characters as appropriate
makeExample :: String -> String -> [String] -> Blocks
makeExample prompt expression result =
    B.para $ B.codeWith ("",["prompt"],[]) prompt
        <> B.space
        <> B.codeWith ([], ["haskell","expr"], []) (trim expression)
        <> B.linebreak
        <> (mconcat $ intersperse B.linebreak $ map coder result')
  where
    -- 1. drop trailing whitespace from the prompt, remember the prefix
    prefix = takeWhile (`elem` " \t") prompt

    -- 2. drop, if possible, the exact same sequence of whitespace
    -- characters from each result line
    --
    -- 3. interpret lines that only contain the string "<BLANKLINE>" as an
    -- empty line
    result' = map (substituteBlankLine . tryStripPrefix prefix) result
      where
        tryStripPrefix xs ys = fromMaybe ys $ stripPrefix xs ys

        substituteBlankLine "<BLANKLINE>" = ""
        substituteBlankLine line          = line
    coder = B.codeWith ([], ["result"], [])