summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2008-07-21 09:52:56 +0000
committerIan Lynagh <igloo@earth.li>2008-07-21 09:52:56 +0000
commit85255a966b21172ce5a26c8a9cb0cdaf7315be95 (patch)
tree8cb07cd434b13f2ad11bf23c143e71f25ddeb0c3 /compiler
parentc1153c7803e311d7b6e7de454ea0156b211281c3 (diff)
downloadhaskell-85255a966b21172ce5a26c8a9cb0cdaf7315be95.tar.gz
Fixes for haddock 0.8
Diffstat (limited to 'compiler')
-rw-r--r--compiler/basicTypes/DataCon.lhs2
-rw-r--r--compiler/cmm/Dataflow.hs10
-rw-r--r--compiler/deSugar/Match.lhs4
-rw-r--r--compiler/ghci/InteractiveUI.hs2
-rw-r--r--compiler/nativeGen/RegAllocColor.hs2
-rw-r--r--compiler/nativeGen/RegAllocLinear.hs2
-rw-r--r--compiler/nativeGen/RegAllocStats.hs8
-rw-r--r--compiler/nativeGen/RegLiveness.hs4
-rw-r--r--compiler/nativeGen/RegSpillClean.hs14
-rw-r--r--compiler/prelude/PrelInfo.lhs2
-rw-r--r--compiler/rename/RnNames.lhs2
-rw-r--r--compiler/stranal/WwLib.lhs10
-rw-r--r--compiler/typecheck/TcInstDcls.lhs6
-rw-r--r--compiler/typecheck/TcMType.lhs6
-rw-r--r--compiler/utils/GraphOps.hs4
15 files changed, 39 insertions, 39 deletions
diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs
index 844c69b555..a9faa2cc7e 100644
--- a/compiler/basicTypes/DataCon.lhs
+++ b/compiler/basicTypes/DataCon.lhs
@@ -275,7 +275,7 @@ data DataCon
-- Reason: less confusing, and easier to generate IfaceSyn
dcEqSpec :: [(TyVar,Type)], -- Equalities derived from the result type,
- -- /as written by the programmer/
+ -- _as written by the programmer_
-- This field allows us to move conveniently between the two ways
-- of representing a GADT constructor's type:
-- MkT :: forall a b. (a :=: [b]) => b -> T a
diff --git a/compiler/cmm/Dataflow.hs b/compiler/cmm/Dataflow.hs
index 35fdebbce4..81934bcb25 100644
--- a/compiler/cmm/Dataflow.hs
+++ b/compiler/cmm/Dataflow.hs
@@ -24,10 +24,10 @@ module Dataflow (
-- that is H*E. The N term of the complexity is from the initial call
-- when 'update' will be passed 'Nothing'.
fixedpoint ::
- (node -> [node]) -- ^ map from nodes to those who's
+ (node -> [node]) -- map from nodes to those who's
-- value depend on the argument node
-> (node -> Maybe node -> s -> Maybe s)
- -- ^ Given the node which needs to be
+ -- Given the node which needs to be
-- updated, and which node caused that node
-- to need to be updated, update the state.
--
@@ -37,13 +37,13 @@ fixedpoint ::
-- Must return 'Nothing' if no change,
-- otherwise returrn 'Just' of the new state.
- -> [node] -- ^ Nodes that should initially be updated
+ -> [node] -- Nodes that should initially be updated
- -> s -- ^ Initial state
+ -> s -- Initial state
-- (usually a map from node to
-- the value for that node)
- -> s -- ^ Final state
+ -> s -- Final state
fixedpoint dependants update nodes state =
foldr (fixedpoint' Nothing) state nodes where
-- Use a depth first traversal of nodes based on the update graph.
diff --git a/compiler/deSugar/Match.lhs b/compiler/deSugar/Match.lhs
index f545930a48..375dec6eb1 100644
--- a/compiler/deSugar/Match.lhs
+++ b/compiler/deSugar/Match.lhs
@@ -242,7 +242,7 @@ Make all constructor patterns in column~1 into @ConPats@, notably
Handle any irrefutable (or ``twiddle'') @LazyPats@.
\end{itemize}
\item
-Now {\em unmix} the equations into {\em blocks} [w/ local function
+Now {\em unmix} the equations into {\em blocks} [w\/ local function
@unmix_eqns@], in which the equations in a block all have variable
patterns in column~1, or they all have constructor patterns in ...
(see ``the mixture rule'' in SLPJ).
@@ -268,7 +268,7 @@ Wadler-chapter @match@ (p.~93, last clause), and @match_unmixed_blk@
corresponds roughly to @matchVarCon@.
\begin{code}
-match :: [Id] -- Variables rep'ing the exprs we're matching with
+match :: [Id] -- Variables rep\'ing the exprs we\'re matching with
-> Type -- Type of the case expression
-> [EquationInfo] -- Info about patterns, etc. (type synonym below)
-> DsM MatchResult -- Desugared result!
diff --git a/compiler/ghci/InteractiveUI.hs b/compiler/ghci/InteractiveUI.hs
index f88fe44995..e1aced2330 100644
--- a/compiler/ghci/InteractiveUI.hs
+++ b/compiler/ghci/InteractiveUI.hs
@@ -2237,7 +2237,7 @@ listModuleLine modl line = do
-- | list a section of a source file around a particular SrcSpan.
-- If the highlight flag is True, also highlight the span using
--- start_bold/end_bold.
+-- start_bold\/end_bold.
listAround :: SrcSpan -> Bool -> IO ()
listAround span do_highlight = do
contents <- BS.readFile (unpackFS file)
diff --git a/compiler/nativeGen/RegAllocColor.hs b/compiler/nativeGen/RegAllocColor.hs
index 30361b20bd..5c8569145f 100644
--- a/compiler/nativeGen/RegAllocColor.hs
+++ b/compiler/nativeGen/RegAllocColor.hs
@@ -33,7 +33,7 @@ import Data.List
import Data.Maybe
import Control.Monad
--- | The maximum number of build/spill cycles we'll allow.
+-- | The maximum number of build\/spill cycles we'll allow.
-- We should only need 3 or 4 cycles tops.
-- If we run for any longer than this we're probably in an infinite loop,
-- It's probably better just to bail out and report a bug at this stage.
diff --git a/compiler/nativeGen/RegAllocLinear.hs b/compiler/nativeGen/RegAllocLinear.hs
index de6e664ac2..815bdfb472 100644
--- a/compiler/nativeGen/RegAllocLinear.hs
+++ b/compiler/nativeGen/RegAllocLinear.hs
@@ -809,7 +809,7 @@ joinToTargets block_live new_blocks instr (dest:dests) = do
joinToTargets block_live (block : new_blocks) instr' dests
--- | Construct a graph of register/spill movements.
+-- | Construct a graph of register\/spill movements.
--
-- We cut some corners by
-- a) not handling cyclic components
diff --git a/compiler/nativeGen/RegAllocStats.hs b/compiler/nativeGen/RegAllocStats.hs
index 58a69fa76e..2c41905811 100644
--- a/compiler/nativeGen/RegAllocStats.hs
+++ b/compiler/nativeGen/RegAllocStats.hs
@@ -58,9 +58,9 @@ data RegAllocStats
, raGraphColored :: Color.Graph Reg RegClass Reg -- ^ the coalesced and colored graph
, raCoalesced :: UniqFM Reg -- ^ the regs that were coaleced
, raPatched :: [LiveCmmTop] -- ^ code with vregs replaced by hregs
- , raSpillClean :: [LiveCmmTop] -- ^ code with unneeded spill/reloads cleaned out
+ , raSpillClean :: [LiveCmmTop] -- ^ code with unneeded spill\/reloads cleaned out
, raFinal :: [NatCmmTop] -- ^ final code
- , raSRMs :: (Int, Int, Int) } -- ^ spill/reload/reg-reg moves present in this code
+ , raSRMs :: (Int, Int, Int) } -- ^ spill\/reload\/reg-reg moves present in this code
instance Outputable RegAllocStats where
@@ -143,7 +143,7 @@ pprStats stats graph
in vcat [outSpills, outLife, outConflict, outScatter]
--- | Dump a table of how many spill loads / stores were inserted for each vreg.
+-- | Dump a table of how many spill loads \/ stores were inserted for each vreg.
pprStatsSpills
:: [RegAllocStats] -> SDoc
@@ -151,7 +151,7 @@ pprStatsSpills stats
= let
finals = [ s | s@RegAllocStatsColored{} <- stats]
- -- sum up how many stores/loads/reg-reg-moves were left in the code
+ -- sum up how many stores\/loads\/reg-reg-moves were left in the code
total = foldl' addSRM (0, 0, 0)
$ map raSRMs finals
diff --git a/compiler/nativeGen/RegLiveness.hs b/compiler/nativeGen/RegLiveness.hs
index dce5de4362..96a264a0b1 100644
--- a/compiler/nativeGen/RegLiveness.hs
+++ b/compiler/nativeGen/RegLiveness.hs
@@ -244,14 +244,14 @@ slurpConflicts live
, moves) lis
--- | For spill/reloads
+-- | For spill\/reloads
--
-- SPILL v1, slot1
-- ...
-- RELOAD slot1, v2
--
-- If we can arrange that v1 and v2 are allocated to the same hreg it's more likely
--- the spill/reload instrs can be cleaned and replaced by a nop reg-reg move.
+-- the spill\/reload instrs can be cleaned and replaced by a nop reg-reg move.
--
--
slurpReloadCoalesce :: LiveCmmTop -> Bag (Reg, Reg)
diff --git a/compiler/nativeGen/RegSpillClean.hs b/compiler/nativeGen/RegSpillClean.hs
index eb0e3eadd6..2ecd4503a7 100644
--- a/compiler/nativeGen/RegSpillClean.hs
+++ b/compiler/nativeGen/RegSpillClean.hs
@@ -1,5 +1,5 @@
{-# OPTIONS -fno-warn-missing-signatures #-}
--- | Clean out unneeded spill/reload instrs
+-- | Clean out unneeded spill\/reload instrs
--
-- * Handling of join points
--
@@ -20,7 +20,7 @@
-- What we really care about here is that on the entry to B3, %r1 will always
-- have the same value that is in SLOT(0) (ie, %r1 is _valid_)
--
--- This also works if the reloads in B1/B2 were spills instead, because
+-- This also works if the reloads in B1\/B2 were spills instead, because
-- spilling %r1 to a slot makes that slot have the same value as %r1.
--
@@ -50,7 +50,7 @@ import Data.List ( find, nub )
type Slot = Int
--- | Clean out unneeded spill/reloads from this top level thing.
+-- | Clean out unneeded spill\/reloads from this top level thing.
cleanSpills :: LiveCmmTop -> LiveCmmTop
cleanSpills cmm
= evalState (cleanSpin 0 cmm) initCleanS
@@ -72,7 +72,7 @@ cleanSpin spinCount code
cleanSpin spinCount code
= do
- -- init count of cleaned spills/reloads
+ -- init count of cleaned spills\/reloads
modify $ \s -> s
{ sCleanedSpillsAcc = 0
, sCleanedReloadsAcc = 0
@@ -86,7 +86,7 @@ cleanSpin spinCount code
-- safe to erase reloads after join points for the next pass.
collateJoinPoints
- -- remember how many spills/reloads we cleaned in this pass
+ -- remember how many spills\/reloads we cleaned in this pass
spills <- gets sCleanedSpillsAcc
reloads <- gets sCleanedReloadsAcc
modify $ \s -> s
@@ -351,10 +351,10 @@ data CleanS
-- reloaded from on this path.
, sReloadedBy :: UniqFM [BlockId]
- -- spills/reloads cleaned each pass (latest at front)
+ -- spills\/reloads cleaned each pass (latest at front)
, sCleanedCount :: [(Int, Int)]
- -- spills/reloads that have been cleaned in this pass so far.
+ -- spills\/reloads that have been cleaned in this pass so far.
, sCleanedSpillsAcc :: Int
, sCleanedReloadsAcc :: Int }
diff --git a/compiler/prelude/PrelInfo.lhs b/compiler/prelude/PrelInfo.lhs
index c8a2322268..96d8c8cb9f 100644
--- a/compiler/prelude/PrelInfo.lhs
+++ b/compiler/prelude/PrelInfo.lhs
@@ -49,7 +49,7 @@ import Array ( Array, array, (!) )
Notes about wired in things
~~~~~~~~~~~~~~~~~~~~~~~~~~~
-* Wired-in things are Ids/TyCons that are completely known to the compiler.
+* Wired-in things are Ids\/TyCons that are completely known to the compiler.
They are global values in GHC, (e.g. listTyCon :: TyCon).
* A wired in Name contains the thing itself inside the Name:
diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs
index 7aad1171c6..5b564c9e75 100644
--- a/compiler/rename/RnNames.lhs
+++ b/compiler/rename/RnNames.lhs
@@ -633,7 +633,7 @@ filterAvail keep ie rest =
let left = filter keep ns in
if null left then rest else AvailTC tc left : rest
--- | Given an import/export spec, construct the appropriate 'GlobalRdrElt's.
+-- | Given an import\/export spec, construct the appropriate 'GlobalRdrElt's.
gresFromIE :: ImpDeclSpec -> (LIE Name, AvailInfo) -> [GlobalRdrElt]
gresFromIE decl_spec (L loc ie, avail)
= gresFromAvail prov_fn avail
diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs
index 19f918f9e1..229c2ece3b 100644
--- a/compiler/stranal/WwLib.lhs
+++ b/compiler/stranal/WwLib.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
%
-\section[WwLib]{A library for the ``worker/wrapper'' back-end to the strictness analyser}
+\section[WwLib]{A library for the ``worker\/wrapper'' back-end to the strictness analyser}
\begin{code}
module WwLib ( mkWwBodies, mkWWstr, mkWorkerArgs ) where
@@ -44,7 +44,7 @@ Here's an example. The original function is:
\begin{verbatim}
g :: forall a . Int -> [a] -> a
-g = /\ a -> \ x ys ->
+g = \/\ a -> \ x ys ->
case x of
0 -> head ys
_ -> head (tail ys)
@@ -55,7 +55,7 @@ From this, we want to produce:
-- wrapper (an unfolding)
g :: forall a . Int -> [a] -> a
-g = /\ a -> \ x ys ->
+g = \/\ a -> \ x ys ->
case x of
I# x# -> $wg a x# ys
-- call the worker; don't forget the type args!
@@ -63,7 +63,7 @@ g = /\ a -> \ x ys ->
-- worker
$wg :: forall a . Int# -> [a] -> a
-$wg = /\ a -> \ x# ys ->
+$wg = \/\ a -> \ x# ys ->
let
x = I# x#
in
@@ -98,7 +98,7 @@ the unusable strictness-info into the interfaces.
%* *
%************************************************************************
-@mkWwBodies@ is called when doing the worker/wrapper split inside a module.
+@mkWwBodies@ is called when doing the worker\/wrapper split inside a module.
\begin{code}
mkWwBodies :: Type -- Type of original function
diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs
index 1f800d9581..daf611af48 100644
--- a/compiler/typecheck/TcInstDcls.lhs
+++ b/compiler/typecheck/TcInstDcls.lhs
@@ -87,9 +87,9 @@ $tau_iop$ is the tau type for this instance of a class method
\item
$alpha$ is the class variable
\item
-$LIE_cop' = LIE_cop [X gammas_bar / alpha, fresh betas_bar]$
+$LIE_cop' = LIE_cop [X gammas_bar \/ alpha, fresh betas_bar]$
\item
-$tau_cop' = tau_cop [X gammas_bar / alpha, fresh betas_bar]$
+$tau_cop' = tau_cop [X gammas_bar \/ alpha, fresh betas_bar]$
\end{enumerate}
ToDo: Update the list above with names actually in the code.
@@ -97,7 +97,7 @@ ToDo: Update the list above with names actually in the code.
\begin{enumerate}
\item
First, make the LIEs for the class and instance contexts, which means
-instantiate $thetaC [X inst_tyvars / alpha ]$, yielding LIElistC' and LIEC',
+instantiate $thetaC [X inst_tyvars \/ alpha ]$, yielding LIElistC' and LIEC',
and make LIElistI and LIEI.
\item
Then process each method in turn.
diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index 4cdbf0131d..43f44b2ad2 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -811,7 +811,7 @@ Consider this:
* Now abstract over the 'a', but float out the Num (C d a) constraint
because it does not 'really' mention a. (see exactTyVarsOfType)
The arg to foo becomes
- /\a -> \t -> t+t
+ \/\a -> \t -> t+t
* So we get a dict binding for Num (C d a), which is zonked to give
a = ()
@@ -820,10 +820,10 @@ Consider this:
quantification, so the floated dict will still have type (C d a).
Which renders this whole note moot; happily!]
-* Then the /\a abstraction has a zonked 'a' in it.
+* Then the \/\a abstraction has a zonked 'a' in it.
All very silly. I think its harmless to ignore the problem. We'll end up with
-a /\a in the final result but all the occurrences of a will be zonked to ()
+a \/\a in the final result but all the occurrences of a will be zonked to ()
Note [Zonking to Skolem]
~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs
index 880f3c65cd..8183e0b299 100644
--- a/compiler/utils/GraphOps.hs
+++ b/compiler/utils/GraphOps.hs
@@ -305,7 +305,7 @@ coalesceGraph' aggressive triv graph kkPairsAcc
pairs -> coalesceGraph' aggressive triv graph' (reverse pairs ++ kkPairsAcc)
--- | Coalesce this pair of nodes unconditionally / agressively.
+-- | Coalesce this pair of nodes unconditionally \/ agressively.
-- The resulting node is the one with the least key.
--
-- returns: Just the pair of keys if the nodes were coalesced
@@ -443,7 +443,7 @@ freezeNode k
-- classes.. this is just a heuristic, after all.
--
-- IDEA: freezing a node might free it up for Simplify.. would be good to check for triv
--- right here, and add it to a worklist if known triv/non-move nodes.
+-- right here, and add it to a worklist if known triv\/non-move nodes.
--
freezeOneInGraph
:: (Uniquable k, Outputable k)