Fix Haddock errors.
authorThomas Schilling <nominolo@googlemail.com>
Sun, 20 Jul 2008 17:30:17 +0000 (17:30 +0000)
committerThomas Schilling <nominolo@googlemail.com>
Sun, 20 Jul 2008 17:30:17 +0000 (17:30 +0000)
compiler/typecheck/FamInst.lhs
compiler/typecheck/TcBinds.lhs
compiler/typecheck/TcHsSyn.lhs
compiler/typecheck/TcRnTypes.lhs
compiler/typecheck/TcSimplify.lhs
compiler/typecheck/TcUnify.lhs

index 8e8df88..89dffbf 100644 (file)
@@ -187,9 +187,9 @@ checkForConflicts inst_envs famInst
           conflictInstErr famInst (head conflicts)
        }
   where
-      -- * In the case of data family instances, any overlap is fundamentally a 
+      -- - In the case of data family instances, any overlap is fundamentally a
       --   conflict (as these instances imply injective type mappings).
-      -- * In the case of type family instances, overlap is admitted as long as 
+      -- - In the case of type family instances, overlap is admitted as long as
       --   the right-hand sides of the overlapping rules coincide under the
       --   overlap substitution.  We require that they are syntactically equal;
       --   anything else would be difficult to test for at this stage.
index 7cafd3c..1e76698 100644 (file)
@@ -860,7 +860,6 @@ checkDistinctTyVars sig_tvs
                          <+> ptext (sLit "is unified with another quantified type variable") 
                          <+> quotes (ppr tidy_tv2)
             ; failWithTcM (env2, msg) }
-       where
 \end{code}
 
 
index e6e95b3..b553453 100644 (file)
@@ -1045,10 +1045,10 @@ mkArbitraryType :: (SrcSpan -> SDoc -> TcRnIf g l a)    -- How to complain
 -- to use when generating a warning
 mkArbitraryType warn tv 
   | liftedTypeKind `isSubKind` kind            -- The vastly common case
-   = return anyPrimTy                  
-  | eqKind kind (tyConKind anyPrimTyCon1)      --  *->*
+  = return anyPrimTy
+  | eqKind kind (tyConKind anyPrimTyCon1)      -- @*->*@
   = return (mkTyConApp anyPrimTyCon1 [])       --     No tuples this size
-  | all isLiftedTypeKind args                  -- *-> ... ->*->*
+  | all isLiftedTypeKind args                  -- @*-> ... ->*->*@
   , isLiftedTypeKind res                       --    Horrible hack to make less use 
   = return (mkTyConApp tup_tc [])              --    of mkAnyPrimTyCon
   | otherwise
index e70161c..3e63827 100644 (file)
@@ -234,9 +234,9 @@ type RecFieldEnv = NameEnv [Name]   -- Maps a constructor name *in this module*
                                        -- to the fields for that constructor
        -- This is used when dealing with ".." notation in record 
        -- construction and pattern matching.
-       -- The FieldEnv deals *only* with constructors defined in
-       -- *thie* module.  For imported modules, we get the same info
-       -- from the TypeEnv
+       -- The FieldEnv deals *only* with constructors defined in *thie*
+       -- module.  For imported modules, we get the same info from the
+       -- TypeEnv
 \end{code}
 
 %************************************************************************
index f651e0f..9ebae01 100644 (file)
@@ -91,34 +91,36 @@ we reduce the (C a b1) constraint from the call of f to (D a b1).
 
 Here is a more complicated example:
 
-| > class Foo a b | a->b
-| >
-| > class Bar a b | a->b
-| >
-| > data Obj = Obj
-| >
-| > instance Bar Obj Obj
-| >
-| > instance (Bar a b) => Foo a b
-| >
-| > foo:: (Foo a b) => a -> String
-| > foo _ = "works"
-| >
-| > runFoo:: (forall a b. (Foo a b) => a -> w) -> w
-| > runFoo f = f Obj
-| 
-| *Test> runFoo foo
-| 
-| <interactive>:1:
-|     Could not deduce (Bar a b) from the context (Foo a b)
-|       arising from use of `foo' at <interactive>:1
-|     Probable fix:
-|         Add (Bar a b) to the expected type of an expression
-|     In the first argument of `runFoo', namely `foo'
-|     In the definition of `it': it = runFoo foo
-| 
-| Why all of the sudden does GHC need the constraint Bar a b? The
-| function foo didn't ask for that... 
+@
+  > class Foo a b | a->b
+  >
+  > class Bar a b | a->b
+  >
+  > data Obj = Obj
+  >
+  > instance Bar Obj Obj
+  >
+  > instance (Bar a b) => Foo a b
+  >
+  > foo:: (Foo a b) => a -> String
+  > foo _ = "works"
+  >
+  > runFoo:: (forall a b. (Foo a b) => a -> w) -> w
+  > runFoo f = f Obj
+
+  *Test> runFoo foo
+
+  <interactive>:1:
+      Could not deduce (Bar a b) from the context (Foo a b)
+        arising from use of `foo' at <interactive>:1
+      Probable fix:
+          Add (Bar a b) to the expected type of an expression
+      In the first argument of `runFoo', namely `foo'
+      In the definition of `it': it = runFoo foo
+
+  Why all of the sudden does GHC need the constraint Bar a b? The
+  function foo didn't ask for that...
+@
 
 The trouble is that to type (runFoo foo), GHC has to solve the problem:
 
@@ -1771,7 +1773,7 @@ reduceContext env wanteds
                ; return init_state
                 }
 
-       -- *** ToDo: what to do with the "extra_givens"?  For the
+       -- !!! ToDo: what to do with the "extra_givens"?  For the
        -- moment I'm simply discarding them, which is probably wrong
 
           -- 6. Solve the *wanted* *dictionary* constraints (not implications)
index 2d9ffc1..ecee5ac 100644 (file)
@@ -1930,7 +1930,7 @@ checkExpectedKind ty act_kind exp_kind
   | otherwise = do
     (_errs, mb_r) <- tryTc (unifyKind exp_kind act_kind)
     case mb_r of
-        Just _  -> return () ;  -- Unification succeeded
+        Just _  -> return ()  -- Unification succeeded
         Nothing -> do
 
         -- So there's definitely an error