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

On branch  : overlapping-tyfams

http://hackage.haskell.org/trac/ghc/changeset/0672eda5fd30b663c32f34e8048ec6a071edf89b

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

commit 0672eda5fd30b663c32f34e8048ec6a071edf89b
Merge: 84fac41... 1baca3e...
Author: Richard Eisenberg <e...@cis.upenn.edu>
Date:   Wed Nov 21 10:40:00 2012 -0500

    Merge branch 'master' into overlapping-tyfams
    
    Conflicts:
        src/Haddock/Convert.hs

 ghc.mk                          |    3 ++-
 src/Haddock/Convert.hs          |   15 +++++++++------
 src/Haddock/Interface.hs        |    4 ++--
 src/Haddock/Interface/Create.hs |    2 +-
 src/Main.hs                     |    4 ++--
 5 files changed, 16 insertions(+), 12 deletions(-)

diff --cc src/Haddock/Convert.hs
index 85749dc,15fba02..6ae5cbb
--- a/src/Haddock/Convert.hs
+++ b/src/Haddock/Convert.hs
@@@ -139,23 -124,21 +139,23 @@@ synifyTyCon t
    = --(why no "isOpenAlgTyCon"?)
      case algTyConRhs tc of
          DataFamilyTyCon ->
 -          TyFamily DataFamily (synifyName tc) (synifyTyVars (tyConTyVars tc))
 -               Nothing --always kind '*'
 -               -- placeHolderKind
 +          FamDecl (FamilyDecl DataFamily (synifyName tc) (synifyTyVars 
(tyConTyVars tc))
 +                              Nothing) --always kind '*'
          _ -> error "synifyTyCon: impossible open data type?"
 +  | isSynTyCon tc
 +  = SynDecl { tcdLName = synifyName tc
 +            , tcdTyVars = synifyTyVars (tyConTyVars tc)
 +            , tcdRhs = synifyType WithinType (synTyConType tc)
 +            , tcdFVs = placeHolderNames }
 +
    | otherwise =
 -  -- (closed) type, newtype, and data
 +  -- (closed) newtype and data
    let
-   nd = if isNewTyCon tc then NewType else DataType
-   ctx = synifyCtx (tyConStupidTheta tc)
 -  -- alg_ only applies to newtype/data
 -  -- syn_ only applies to type
 -  -- others apply to both
+   alg_nd = if isNewTyCon tc then NewType else DataType
+   alg_ctx = synifyCtx (tyConStupidTheta tc)
    name = synifyName tc
    tyvars = synifyTyVars (tyConTyVars tc)
 -  alg_kindSig = Just (tyConKind tc)
 +  kindSig = Just (tyConKind tc)
    -- The data constructors.
    --
    -- Any data-constructors not exported from the module that *defines* the
@@@ -172,18 -155,19 +172,21 @@@
    -- That seems like an acceptable compromise (they'll just be documented
    -- in prefix position), since, otherwise, the logic (at best) gets much more
    -- complicated. (would use dataConIsInfix.)
 -  alg_use_gadt_syntax = any (not . isVanillaDataCon) (tyConDataCons tc)
 -  alg_cons = map (synifyDataCon alg_use_gadt_syntax) (tyConDataCons tc)
 +  use_gadt_syntax = any (not . isVanillaDataCon) (tyConDataCons tc)
 +  cons = map (synifyDataCon use_gadt_syntax) (tyConDataCons tc)
    -- "deriving" doesn't affect the signature, no need to specify any.
-   deriv = Nothing
-   defn = HsDataDefn { dd_ND      = nd
-                     , dd_ctxt    = ctx
+   alg_deriv = Nothing
+   defn | Just (_, syn_rhs) <- synTyConDefn_maybe tc 
+        = TySynonym (synifyType WithinType syn_rhs)
 -       | otherwise = TyData { td_ND = alg_nd, td_ctxt = alg_ctx
 -                            , td_cType = Nothing
 -                            , td_kindSig = fmap synifyKindSig alg_kindSig
 -                            , td_cons    = alg_cons 
 -                            , td_derivs  = alg_deriv }
 - in TyDecl { tcdLName = name, tcdTyVars = tyvars, tcdTyDefn = defn
 -           , tcdFVs = placeHolderNames }
++       | otherwise
++       = HsDataDefn { dd_ND      = alg_nd
++                    , dd_ctxt    = alg_ctx
 +                    , dd_cType   = Nothing
 +                    , dd_kindSig = fmap synifyKindSig kindSig
 +                    , dd_cons    = cons 
-                     , dd_derivs  = deriv }
++                    , dd_derivs  = alg_deriv }
 + in DataDecl { tcdLName = name, tcdTyVars = tyvars, tcdDataDefn = defn
 +             , tcdFVs = placeHolderNames }
  
  -- User beware: it is your responsibility to pass True (use_gadt_syntax)
  -- for any constructor that would be misrepresented by omitting its



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to