[[project @ 2005-02-23 13:46:43 by simonpj] simonpj**20050223134646 --------------------------------------------- Make type synonyms uniform with data types so far as infix operators are concerned --------------------------------------------- Merge to STABLE This allows type (a :+: b) c d = ... which was prevented before by accident. I've also documented the fact that classes can be infix; and arranged that class constraints in types can be in infix form. f :: (a :=: b) => .... ] { hunk ./ghc/compiler/parser/Parser.y.pp 19 -import HscTypes ( ModIface, IsBootInterface, DeprecTxt ) +import HscTypes ( IsBootInterface, DeprecTxt ) hunk ./ghc/compiler/parser/Parser.y.pp 39 -import Bag ( emptyBag ) hunk ./ghc/compiler/parser/Parser.y.pp 439 - : 'type' syn_hdr '=' ctype - -- Note ctype, not sigtype. + : 'type' type '=' ctype + -- Note type on the left of the '='; this allows + -- infix type constructors to be declared + -- + -- Note ctype, not sigtype, on the right hunk ./ghc/compiler/parser/Parser.y.pp 447 - { LL $ let (tc,tvs) = $2 in TySynonym tc tvs $4 } + {% do { (tc,tvs) <- checkSynHdr $2 + ; return (LL (TySynonym tc tvs $4)) } } hunk ./ghc/compiler/parser/Parser.y.pp 451 - { L (comb4 $1 $2 $3 $4) + { L (comb4 $1 $2 $3 $4) -- We need the location on tycl_hdr + -- in case constrs and deriving are both empty hunk ./ghc/compiler/parser/Parser.y.pp 474 -syn_hdr :: { (Located RdrName, [LHsTyVarBndr RdrName]) } - -- We don't retain the syntax of an infix - -- type synonym declaration. Oh well. - : tycon tv_bndrs { ($1, $2) } - | tv_bndr tyconop tv_bndr { ($2, [$1,$3]) } - hunk ./ghc/compiler/parser/Parser.y.pp 481 - : context '=>' type {% checkTyClHdr $1 $3 >>= return.LL } + : context '=>' type {% checkTyClHdr $1 $3 >>= return.LL } hunk ./ghc/compiler/parser/RdrHsSyn.lhs 37 - , checkTyClHdr -- HsType -> (name,[tyvar]) + , checkTyClHdr + , checkSynHdr hunk ./ghc/compiler/parser/RdrHsSyn.lhs 52 -import IfaceType -import Packages ( PackageIdH(..) ) -import HscTypes ( ModIface(..), emptyModIface, mkIfaceVerCache, - Dependencies(..), IsBootInterface, noDependencies ) -import IfaceSyn ( IfaceDecl(..), IfaceIdInfo(..), IfaceConDecl(..), IfaceConDecls(..) ) hunk ./ghc/compiler/parser/RdrHsSyn.lhs 54 - setRdrNameSpace, rdrNameModule ) -import BasicTypes ( RecFlag(..), mapIPName, maxPrecedence, initialVersion ) + setRdrNameSpace ) +import BasicTypes ( RecFlag(..), maxPrecedence ) hunk ./ghc/compiler/parser/RdrHsSyn.lhs 57 -import Kind ( liftedTypeKind ) -import HscTypes ( GenAvailInfo(..) ) hunk ./ghc/compiler/parser/RdrHsSyn.lhs 60 -import OccName ( OccName, srcDataName, varName, isDataOcc, isTcOcc, - occNameUserString, isValOcc ) -import BasicTypes ( initialVersion, StrictnessMark(..) ) -import Module ( Module ) +import OccName ( srcDataName, varName, isDataOcc, isTcOcc, + occNameUserString ) hunk ./ghc/compiler/parser/RdrHsSyn.lhs 384 +checkSynHdr :: LHsType RdrName -> P (Located RdrName, [LHsTyVarBndr RdrName]) +checkSynHdr ty = do { (_, tc, tvs) <- checkTyClHdr (noLoc []) ty + ; return (tc, tvs) } + hunk ./ghc/compiler/parser/RdrHsSyn.lhs 449 - check loc (HsTyVar t) args | not (isRdrTyVar t) - = return (L spn (HsClassP t args)) - check loc (HsAppTy l r) args = checkl l (r:args) - check loc (HsParTy t) args = checkl t args - check loc _ _ = parseError loc "malformed class assertion" + check _loc (HsTyVar t) args | not (isRdrTyVar t) + = return (L spn (HsClassP t args)) + check _loc (HsAppTy l r) args = checkl l (r:args) + check _loc (HsOpTy l (L loc tc) r) args = check loc (HsTyVar tc) (l:r:args) + check _loc (HsParTy t) args = checkl t args + check loc _ _ = parseError loc "malformed class assertion" hunk ./ghc/docs/users_guide/glasgow_exts.xml 928 -Infix type constructors +Infix type constructors and classes hunk ./ghc/docs/users_guide/glasgow_exts.xml 931 -GHC allows type constructors to be operators, and to be written infix, very much +GHC allows type constructors and classes to be operators, and to be written infix, very much hunk ./ghc/docs/users_guide/glasgow_exts.xml 935 - A type constructor can be an operator, beginning with a colon; e.g. :*:. + A type constructor or class can be an operator, beginning with a colon; e.g. :*:. hunk ./ghc/docs/users_guide/glasgow_exts.xml 939 - Types can be written infix. For example Int :*: Bool. + Data type and type-synonym declarations can be written infix, parenthesised + if you want further arguments. E.g. + + data a :*: b = Foo a b + type a :+: b = Either a b + class a :=: b where ... + + data (a :**: b) x = Baz a b x + type (a :++: b) y = Either (a,b) y + + + + Types, and class constraints, can be written infix. For example + + x :: Int :*: Bool + f :: (a :=: b) => a -> b + hunk ./ghc/docs/users_guide/glasgow_exts.xml 963 - Fixities may be declared for type constructors just as for data constructors. However, + Fixities may be declared for type constructors, or classes, just as for data constructors. However, hunk ./ghc/docs/users_guide/glasgow_exts.xml 976 - - Data type and type-synonym declarations can be written infix. E.g. - - data a :*: b = Foo a b - type a :+: b = Either a b - - }