Skip to content
Snippets Groups Projects
Commit 68a78932 authored by Niklas Haas's avatar Niklas Haas
Browse files

Group similar fixities together

Identical fixities declared for the same line should now render using
syntax like: infix 4 <, >=, >, <=
parent 003f1179
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
...@@ -144,7 +144,19 @@ window.onload = function () {pageLoad();setSynopsis("mini_Operators.html");}; ...@@ -144,7 +144,19 @@ window.onload = function () {pageLoad();setSynopsis("mini_Operators.html");};
><li ><li
><a href="#v:-62--62--60-" ><a href="#v:-62--62--60-"
>(&gt;&gt;&lt;)</a >(&gt;&gt;&lt;)</a
>, <a href="#v:-60--60--62-"
>(&lt;&lt;&gt;)</a
> :: a -&gt; b -&gt; ()</li > :: a -&gt; b -&gt; ()</li
><li
><a href="#v:-42--42--62-"
>(**&gt;)</a
>, <a href="#v:-60--42--42-"
>(&lt;**)</a
>, <a href="#v:-62--42--42-"
>(&gt;**)</a
>, <a href="#v:-42--42--60-"
>(**&lt;)</a
> :: a -&gt; a -&gt; ()</li
></ul ></ul
></li ></li
><li class="src short" ><li class="src short"
...@@ -345,10 +357,29 @@ window.onload = function () {pageLoad();setSynopsis("mini_Operators.html");}; ...@@ -345,10 +357,29 @@ window.onload = function () {pageLoad();setSynopsis("mini_Operators.html");};
><p class="caption" ><p class="caption"
>Methods</p >Methods</p
><p class="src" ><p class="src"
>infixr 4 &gt;&gt;&lt;<br >infixl 5 &lt;&lt;&gt;<br
/>infixr 4 &gt;&gt;&lt;<br
/><a name="v:-62--62--60-" class="def" /><a name="v:-62--62--60-" class="def"
>(&gt;&gt;&lt;)</a >(&gt;&gt;&lt;)</a
>, <a name="v:-60--60--62-" class="def"
>(&lt;&lt;&gt;)</a
> :: a -&gt; b -&gt; ()</p > :: a -&gt; b -&gt; ()</p
><p class="src"
>infixr 8 **&gt;, &gt;**<br
/>infixl 8 &lt;**, **&lt;<br
/><a name="v:-42--42--62-" class="def"
>(**&gt;)</a
>, <a name="v:-60--42--42-" class="def"
>(&lt;**)</a
>, <a name="v:-62--42--42-" class="def"
>(&gt;**)</a
>, <a name="v:-42--42--60-" class="def"
>(**&lt;)</a
> :: a -&gt; a -&gt; ()</p
><div class="doc"
><p
>Multiple fixities</p
></div
></div ></div
></div ></div
><div class="top" ><div class="top"
......
...@@ -45,11 +45,19 @@ infix 9 ** ...@@ -45,11 +45,19 @@ infix 9 **
class a ><> b where class a ><> b where
type a <>< b :: * type a <>< b :: *
data a ><< b data a ><< b
(>><) :: a -> b -> () (>><), (<<>) :: a -> b -> ()
-- | Multiple fixities
(**>), (**<), (>**), (<**) :: a -> a -> ()
infixr 1 ><> infixr 1 ><>
infixl 2 <>< infixl 2 <><
infixl 3 ><< infixl 3 ><<
infixr 4 >>< infixr 4 >><
infixl 5 <<>
infixr 8 **>, >**
infixl 8 **<, <**
-- | Type synonym with fixity -- | Type synonym with fixity
type (a >-< b) = a <-> b type (a >-< b) = a <-> b
......
{-# LANGUAGE TransformListComp #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : Haddock.Backends.Html.Decl -- Module : Haddock.Backends.Html.Decl
...@@ -34,6 +35,7 @@ import Data.Monoid ( mempty ) ...@@ -34,6 +35,7 @@ import Data.Monoid ( mempty )
import Text.XHtml hiding ( name, title, p, quote ) import Text.XHtml hiding ( name, title, p, quote )
import GHC import GHC
import GHC.Exts
import Name import Name
...@@ -158,15 +160,20 @@ ppTypeOrFunSig summary links loc docnames typ (doc, argDocs) (pref1, pref2, sep) ...@@ -158,15 +160,20 @@ ppTypeOrFunSig summary links loc docnames typ (doc, argDocs) (pref1, pref2, sep)
= [(leader <+> ppType unicode qual t, argDoc n, [])] = [(leader <+> ppType unicode qual t, argDoc n, [])]
ppFixities :: [(DocName, Fixity)] -> Qualification -> Html ppFixities :: [(DocName, Fixity)] -> Qualification -> Html
ppFixities fs qual = vcat $ map ppFix fs ppFixities fs qual = vcat $ map ppFix uniq_fs
where where
ppFix (n, Fixity p d) = toHtml (ppDir d) <+> toHtml (show p) ppFix (ns, p, d) = toHtml d <+> toHtml (show p) <+> ppNames ns
<+> ppDocName qual Infix False n
ppDir InfixR = "infixr" ppDir InfixR = "infixr"
ppDir InfixL = "infixl" ppDir InfixL = "infixl"
ppDir InfixN = "infix" ppDir InfixN = "infix"
ppNames = concatHtml . intersperse (stringToHtml ", ") . map (ppDocName qual Infix False)
uniq_fs = [ (n, the p, the d') | (n, Fixity p d) <- fs
, let d' = ppDir d
, then group by Down (p,d') using groupWith ]
ppTyVars :: LHsTyVarBndrs DocName -> [Html] ppTyVars :: LHsTyVarBndrs DocName -> [Html]
ppTyVars tvs = map ppTyName (tyvarNames tvs) ppTyVars tvs = map ppTyName (tyvarNames tvs)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment