Repository : ssh://darcs.haskell.org//srv/darcs/haddock

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/8b2ee333020aeb9e639cd1772e1dca3b4b4ef3d2

>---------------------------------------------------------------

commit 8b2ee333020aeb9e639cd1772e1dca3b4b4ef3d2
Author: Ian Lynagh <[email protected]>
Date:   Sat Oct 1 01:34:06 2011 +0100

    Follow changes to ForeignImport/ForeignExport in GHC

>---------------------------------------------------------------

 src/Haddock/Backends/Hoogle.hs            |    4 ++--
 src/Haddock/Backends/Xhtml/Decl.hs        |    2 +-
 src/Haddock/GhcUtils.hs                   |    4 ++--
 src/Haddock/Interface/Create.hs           |    2 +-
 src/Haddock/Interface/ExtractFnArgDocs.hs |    2 +-
 src/Haddock/Interface/Rename.hs           |    8 ++++----
 6 files changed, 11 insertions(+), 11 deletions(-)

diff --git a/src/Haddock/Backends/Hoogle.hs b/src/Haddock/Backends/Hoogle.hs
index adf9563..4539996 100644
--- a/src/Haddock/Backends/Hoogle.hs
+++ b/src/Haddock/Backends/Hoogle.hs
@@ -114,8 +114,8 @@ ppExport (ExportDecl decl dc subdocs _) = doc (fst dc) ++ f 
(unL decl)
         f (TyClD d@TyData{}) = ppData d subdocs
         f (TyClD d@ClassDecl{}) = ppClass d
         f (TyClD d@TySynonym{}) = ppSynonym d
-        f (ForD (ForeignImport name typ _)) = ppSig $ TypeSig [name] typ
-        f (ForD (ForeignExport name typ _)) = ppSig $ TypeSig [name] typ
+        f (ForD (ForeignImport name typ _ _)) = ppSig $ TypeSig [name] typ
+        f (ForD (ForeignExport name typ _ _)) = ppSig $ TypeSig [name] typ
         f (SigD sig) = ppSig sig
         f _ = []
 ppExport _ = []
diff --git a/src/Haddock/Backends/Xhtml/Decl.hs 
b/src/Haddock/Backends/Xhtml/Decl.hs
index 2813204..c1f3a89 100644
--- a/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/src/Haddock/Backends/Xhtml/Decl.hs
@@ -114,7 +114,7 @@ tyvarNames = map (getName . hsTyVarName . unLoc)
 
 ppFor :: Bool -> LinksInfo -> SrcSpan -> DocForDecl DocName
       -> ForeignDecl DocName -> Bool -> Qualification -> Html
-ppFor summary links loc doc (ForeignImport (L _ name) (L _ typ) _) unicode qual
+ppFor summary links loc doc (ForeignImport (L _ name) (L _ typ) _ _) unicode 
qual
   = ppFunSig summary links loc doc [name] typ unicode qual
 ppFor _ _ _ _ _ _ _ = error "ppFor"
 
diff --git a/src/Haddock/GhcUtils.hs b/src/Haddock/GhcUtils.hs
index f79acd9..33ae1b6 100644
--- a/src/Haddock/GhcUtils.hs
+++ b/src/Haddock/GhcUtils.hs
@@ -96,8 +96,8 @@ getMainDeclBinder (ValD d) =
 #endif
 
 getMainDeclBinder (SigD d) = sigNameNoLoc d
-getMainDeclBinder (ForD (ForeignImport name _ _)) = [unLoc name]
-getMainDeclBinder (ForD (ForeignExport _ _ _)) = []
+getMainDeclBinder (ForD (ForeignImport name _ _ _)) = [unLoc name]
+getMainDeclBinder (ForD (ForeignExport _ _ _ _)) = []
 getMainDeclBinder _ = []
 
 -- Useful when there is a signature with multiple names, e.g.
diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs
index 860a004..057fceb 100644
--- a/src/Haddock/Interface/Create.hs
+++ b/src/Haddock/Interface/Create.hs
@@ -263,7 +263,7 @@ declsFromClass class_ = docs ++ defs ++ sigs ++ ats
 
 declNames :: HsDecl a -> [a]
 declNames (TyClD d) = [tcdName d]
-declNames (ForD (ForeignImport n _ _)) = [unLoc n]
+declNames (ForD (ForeignImport n _ _ _)) = [unLoc n]
 -- we have normal sigs only (since they are taken from ValBindsOut)
 declNames (SigD sig) = sigNameNoLoc sig
 declNames _ = error "unexpected argument to declNames"
diff --git a/src/Haddock/Interface/ExtractFnArgDocs.hs 
b/src/Haddock/Interface/ExtractFnArgDocs.hs
index 8889c3a..a9f8a80 100644
--- a/src/Haddock/Interface/ExtractFnArgDocs.hs
+++ b/src/Haddock/Interface/ExtractFnArgDocs.hs
@@ -24,7 +24,7 @@ import GHC
 
 getDeclFnArgDocs :: HsDecl Name -> Map Int HsDocString
 getDeclFnArgDocs (SigD (TypeSig _ ty)) = getTypeFnArgDocs ty
-getDeclFnArgDocs (ForD (ForeignImport _ ty _)) = getTypeFnArgDocs ty
+getDeclFnArgDocs (ForD (ForeignImport _ ty _ _)) = getTypeFnArgDocs ty
 getDeclFnArgDocs (TyClD (TySynonym {tcdSynRhs = ty})) = getTypeFnArgDocs ty
 getDeclFnArgDocs _ = Map.empty
 
diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs
index 4ea22a2..546ba62 100644
--- a/src/Haddock/Interface/Rename.hs
+++ b/src/Haddock/Interface/Rename.hs
@@ -392,14 +392,14 @@ renameSig sig = case sig of
 
 
 renameForD :: ForeignDecl Name -> RnM (ForeignDecl DocName)
-renameForD (ForeignImport lname ltype x) = do
+renameForD (ForeignImport lname ltype co x) = do
   lname' <- renameL lname
   ltype' <- renameLType ltype
-  return (ForeignImport lname' ltype' x)
-renameForD (ForeignExport lname ltype x) = do
+  return (ForeignImport lname' ltype' co x)
+renameForD (ForeignExport lname ltype co x) = do
   lname' <- renameL lname
   ltype' <- renameLType ltype
-  return (ForeignExport lname' ltype' x)
+  return (ForeignExport lname' ltype' co x)
 
 
 renameInstD :: InstDecl Name -> RnM (InstDecl DocName)



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to