| Quick question - is it possible to put type class contexts on
| existentially quantified variables in GADTs defined using record syntax?

Audrey Tang implemented the ability to use record syntax for GADTs.  Looks as 
if she didn't finish. I see the code below in Parser.y.pp. Note the 
commented-out code.  It looks as if her *intention* was to allow
                forall a. Eq a => D { x,y :: a } :: T a
but she didn't do that for some reason.  My guess: she got reduce/reduce errors 
and never came back to it


In short, I think the only obstacle here is parsing.  Would someone like to 
have a go?  And/or file a feature request?

Simon


-- We allow the following forms:
--      C :: Eq a => a -> T a
--      C :: forall a. Eq a => !a -> T a
--      D { x,y :: a } :: T a
--      forall a. Eq a => D { x,y :: a } :: T a

gadt_constr :: { LConDecl RdrName }
        : con '::' sigtype
              { LL (mkGadtDecl $1 $3) }
        -- Syntax: Maybe merge the record stuff with the single-case above?
        --         (to kill the mostly harmless reduce/reduce error)
        -- XXX revisit audreyt
        | constr_stuff_record '::' sigtype
                { let (con,details) = unLoc $1 in
                  LL (ConDecl con Implicit [] (noLoc []) details (ResTyGADT $3) 
Nothing) }
{-
        | forall context '=>' constr_stuff_record '::' sigtype
                { let (con,details) = unLoc $4 in
                  LL (ConDecl con Implicit (unLoc $1) $2 details (ResTyGADT $6) 
Nothing ) }
        | forall constr_stuff_record '::' sigtype
                { let (con,details) = unLoc $2 in
                  LL (ConDecl con Implicit (unLoc $1) (noLoc []) details 
(ResTyGADT $4) Nothing) }
-}


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

Reply via email to