Comments only: replace ":=:" by "~" (notation for equality predicates)
[ghc-hetmet.git] / compiler / basicTypes / DataCon.lhs
index a01cf74..1b354c6 100644 (file)
@@ -19,8 +19,7 @@ module DataCon (
        dataConUnivTyVars, dataConExTyVars, dataConAllTyVars, 
        dataConEqSpec, eqSpecPreds, dataConEqTheta, dataConDictTheta, dataConStupidTheta, 
        dataConInstArgTys, dataConOrigArgTys, dataConOrigResTy,
-       dataConInstOrigArgTys, dataConInstOrigDictsAndArgTys,
-       dataConRepArgTys, 
+       dataConInstOrigArgTys, dataConRepArgTys, 
        dataConFieldLabels, dataConFieldType,
        dataConStrictMarks, dataConExStricts,
        dataConSourceArity, dataConRepArity,
@@ -165,7 +164,7 @@ Why might the wrapper have anything to do?  Two reasons:
        \$wMkT :: a -> T [a]
        \$wMkT a x = MkT [a] a [a] x
   The third argument is a coerion
-       [a] :: [a]:=:[a]
+       [a] :: [a]~[a]
 
 INVARIANT: the dictionary constructor for a class
           never has a wrapper.
@@ -247,14 +246,14 @@ data DataCon
 
        --      *** As represented internally
        --  data T a where
-       --    MkT :: forall a. forall x y. (a:=:(x,y),x~y,Ord x) => x -> y -> T a
+       --    MkT :: forall a. forall x y. (a~(x,y),x~y,Ord x) => x -> y -> T a
        -- 
        -- The next six fields express the type of the constructor, in pieces
        -- e.g.
        --
        --      dcUnivTyVars  = [a]
        --      dcExTyVars    = [x,y]
-       --      dcEqSpec      = [a:=:(x,y)]
+       --      dcEqSpec      = [a~(x,y)]
        --      dcEqTheta     = [x~y]   
        --      dcDictTheta   = [Ord x]
        --      dcOrigArgTys  = [a,List b]
@@ -287,9 +286,9 @@ data DataCon
                                        -- _as written by the programmer_
                -- This field allows us to move conveniently between the two ways
                -- of representing a GADT constructor's type:
-               --      MkT :: forall a b. (a :=: [b]) => b -> T a
+               --      MkT :: forall a b. (a ~ [b]) => b -> T a
                --      MkT :: forall b. b -> T [b]
-               -- Each equality is of the form (a :=: ty), where 'a' is one of 
+               -- Each equality is of the form (a ~ ty), where 'a' is one of 
                -- the universally quantified type variables
                                        
                -- The next two fields give the type context of the data constructor
@@ -347,7 +346,7 @@ data DataCon
        dcRepTyCon  :: TyCon,           -- Result tycon, T
 
        dcRepType   :: Type,    -- Type of the constructor
-                               --      forall a x y. (a:=:(x,y), x~y, Ord x) =>
+                               --      forall a x y. (a~(x,y), x~y, Ord x) =>
                                 --        x -> y -> T a
                                -- (this is *not* of the constructor wrapper Id:
                                --  see Note [Data con representation] below)
@@ -356,7 +355,7 @@ data DataCon
        --      case (e :: T t) of
         --        MkT x y co1 co2 (d:Ord x) (v:r) (w:F s) -> ...
        -- It's convenient to apply the rep-type of MkT to 't', to get
-       --      forall x y. (t:=:(x,y), x~y, Ord x) => x -> y -> T t
+       --      forall x y. (t~(x,y), x~y, Ord x) => x -> y -> T t
        -- and use that to check the pattern.  Mind you, this is really only
        -- used in CoreLint.
 
@@ -761,8 +760,8 @@ dataConInstArgTys dc@(MkData {dcRepArgTys = rep_arg_tys,
    ASSERT2 ( null ex_tvs && null eq_spec, ppr dc )        
    map (substTyWith univ_tvs inst_tys) rep_arg_tys
 
--- | Returns just the instantiated /value/ arguments of a 'DataCon',
--- as opposed to including the dictionary args as in 'dataConInstOrigDictsAndArgTys'
+-- | Returns just the instantiated /value/ argument types of a 'DataCon',
+-- (excluding dictionary args)
 dataConInstOrigArgTys 
        :: DataCon      -- Works for any DataCon
        -> [Type]       -- Includes existential tyvar args, but NOT
@@ -778,23 +777,6 @@ dataConInstOrigArgTys dc@(MkData {dcOrigArgTys = arg_tys,
     map (substTyWith tyvars inst_tys) arg_tys
   where
     tyvars = univ_tvs ++ ex_tvs
-
--- | Returns just the instantiated dicts and /value/ arguments for a 'DataCon',
--- as opposed to excluding the dictionary args as in 'dataConInstOrigArgTys'
-dataConInstOrigDictsAndArgTys 
-       :: DataCon      -- Works for any DataCon
-       -> [Type]       -- Includes existential tyvar args, but NOT
-                       -- equality constraints or dicts
-       -> [Type]
-dataConInstOrigDictsAndArgTys dc@(MkData {dcOrigArgTys = arg_tys,
-                                 dcDictTheta = dicts,       
-                                 dcUnivTyVars = univ_tvs, 
-                                 dcExTyVars = ex_tvs}) inst_tys
-  = ASSERT2( length tyvars == length inst_tys
-          , ptext (sLit "dataConInstOrigDictsAndArgTys") <+> ppr dc $$ ppr tyvars $$ ppr inst_tys )
-    map (substTyWith tyvars inst_tys) (mkPredTys dicts ++ arg_tys)
-  where
-    tyvars = univ_tvs ++ ex_tvs
 \end{code}
 
 \begin{code}
@@ -818,7 +800,7 @@ dataConIdentity dc = bytesFS (packageIdFS (modulePackageId mod)) ++
                   fromIntegral (ord ':') : bytesFS (moduleNameFS (moduleName mod)) ++
                   fromIntegral (ord '.') : bytesFS (occNameFS (nameOccName name))
   where name = dataConName dc
-        mod  = nameModule name
+        mod  = ASSERT( isExternalName name ) nameModule name
 \end{code}
 
 \begin{code}