2 -- The above warning supression flag is a temporary kludge.
3 -- While working on this module you are encouraged to remove it and fix
4 -- any warnings in the module. See
5 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
8 module HaddockUtils where
12 import {-# SOURCE #-} HaddockLex
22 -- -----------------------------------------------------------------------------
23 -- Parsing module headers
25 -- NB. The headers must be given in the order Module, Description,
26 -- Copyright, License, Maintainer, Stability, Portability, except that
27 -- any or all may be omitted.
28 parseModuleHeader :: String -> Either String (String, HaddockModInfo RdrName)
29 parseModuleHeader str0 =
31 getKey :: String -> String -> (Maybe String,String)
32 getKey key str = case parseKey key str of
33 Nothing -> (Nothing,str)
34 Just (value,rest) -> (Just value,rest)
36 (moduleOpt,str1) = getKey "Module" str0
37 (descriptionOpt,str2) = getKey "Description" str1
38 (copyrightOpt,str3) = getKey "Copyright" str2
39 (licenseOpt,str4) = getKey "License" str3
40 (licenceOpt,str5) = getKey "Licence" str4
41 (maintainerOpt,str6) = getKey "Maintainer" str5
42 (stabilityOpt,str7) = getKey "Stability" str6
43 (portabilityOpt,str8) = getKey "Portability" str7
45 description1 :: Either String (Maybe (HsDoc RdrName))
46 description1 = case descriptionOpt of
47 Nothing -> Right Nothing
48 Just description -> case parseHaddockString . tokenise $ description of
50 MyLeft mess -> Left ("Cannot parse Description: " ++ mess)
51 MyRight doc -> Right (Just doc)
54 Left mess -> Left mess
55 Right docOpt -> Right (str8,HaddockModInfo {
56 hmi_description = docOpt,
57 hmi_portability = portabilityOpt,
58 hmi_stability = stabilityOpt,
59 hmi_maintainer = maintainerOpt
62 -- | This function is how we read keys.
64 -- all fields in the header are optional and have the form
66 -- [spaces1][field name][spaces] ":"
67 -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")*
68 -- where each [spaces2] should have [spaces1] as a prefix.
70 -- Thus for the key "Description",
72 -- > Description : this is a
77 -- > The module comment starts here
79 -- the value will be "this is a .. description" and the rest will begin
80 -- at "The module comment".
81 parseKey :: String -> String -> Maybe (String,String)
82 parseKey key toParse0 =
85 (spaces0,toParse1) = extractLeadingSpaces toParse0
88 afterKey0 <- extractPrefix key toParse1
90 afterKey1 = extractLeadingSpaces afterKey0
91 afterColon0 <- case snd afterKey1 of
92 ':':afterColon -> return afterColon
95 (_,afterColon1) = extractLeadingSpaces afterColon0
97 return (scanKey True indentation afterColon1)
99 scanKey :: Bool -> String -> String -> (String,String)
100 scanKey isFirst indentation [] = ([],[])
101 scanKey isFirst indentation str =
103 (nextLine,rest1) = extractNextLine str
105 accept = isFirst || sufficientIndentation || allSpaces
107 sufficientIndentation = case extractPrefix indentation nextLine of
108 Just (c:_) | isSpace c -> True
111 allSpaces = case extractLeadingSpaces nextLine of
118 (scanned1,rest2) = scanKey False indentation rest1
120 scanned2 = case scanned1 of
121 "" -> if allSpaces then "" else nextLine
122 _ -> nextLine ++ "\n" ++ scanned1
128 extractLeadingSpaces :: String -> (String,String)
129 extractLeadingSpaces [] = ([],[])
130 extractLeadingSpaces (s@(c:cs))
133 (spaces1,cs1) = extractLeadingSpaces cs
138 extractNextLine :: String -> (String,String)
139 extractNextLine [] = ([],[])
140 extractNextLine (c:cs)
145 (line,rest) = extractNextLine cs
150 -- indentation returns characters after last newline.
151 indentation :: String -> String
152 indentation s = fromMaybe s (indentation0 s)
154 indentation0 :: String -> Maybe String
155 indentation0 [] = Nothing
156 indentation0 (c:cs) =
157 case indentation0 cs of
158 Nothing -> if c == '\n' then Just cs else Nothing
161 -- comparison is case-insensitive.
162 extractPrefix :: String -> String -> Maybe String
163 extractPrefix [] s = Just s
164 extractPrefix s [] = Nothing
165 extractPrefix (c1:cs1) (c2:cs2)
166 | toUpper c1 == toUpper c2 = extractPrefix cs1 cs2
169 -- -----------------------------------------------------------------------------
170 -- Adding documentation to record fields (used in parsing).
172 type Field a = ([Located a], LBangType a, Maybe (LHsDoc a))
174 addFieldDoc :: Field a -> Maybe (LHsDoc a) -> Field a
175 addFieldDoc (a, b, c) doc = (a, b, c `mplus` doc)
177 addFieldDocs :: [Field a] -> Maybe (LHsDoc a) -> [Field a]
178 addFieldDocs [] _ = []
179 addFieldDocs (x:xs) doc = addFieldDoc x doc : xs
181 addConDoc :: LConDecl a -> Maybe (LHsDoc a) -> LConDecl a
182 addConDoc (L p c) doc = L p ( c { con_doc = con_doc c `mplus` doc } )
184 addConDocs :: [LConDecl a] -> Maybe (LHsDoc a) -> [LConDecl a]
186 addConDocs [x] doc = [addConDoc x doc]
187 addConDocs (x:xs) doc = x : addConDocs xs doc
189 addConDocFirst :: [LConDecl a] -> Maybe (LHsDoc a) -> [LConDecl a]
190 addConDocFirst [] _ = []
191 addConDocFirst (x:xs) doc = addConDoc x doc : xs