Rename maybeTyConSingleCon to tyConSingleDataCon_maybe
[ghc-hetmet.git] / compiler / types / TyCon.lhs
index 88a6209..d7347a8 100644 (file)
@@ -11,7 +11,7 @@ module TyCon(
 
        PrimRep(..),
        tyConPrimRep,
-        sizeofPrimRep,
+        primRepSizeW,
 
        AlgTyConRhs(..), visibleDataCons, 
         TyConParent(..), 
@@ -61,7 +61,7 @@ module TyCon(
        synTyConDefn, synTyConRhs, synTyConType, synTyConResKind,
        tyConExtName,           -- External name for foreign types
 
-        maybeTyConSingleCon,
+        tyConSingleDataCon_maybe,
 
        -- Generics
         tyConHasGenerics
@@ -186,7 +186,7 @@ data TyCon
         tyConName   :: Name,
        tyConArity  :: Arity,
        coKindFun   :: [Type] -> (Type,Type)
-    }          -- INVARAINT: coKindFun is always applied to exactly 'arity' args
+    }          -- INVARIANT: coKindFun is always applied to exactly 'arity' args
                -- E.g. for trans (c1 :: ta=tb) (c2 :: tb=tc), the coKindFun returns 
                --      the kind as a pair of types: (ta,tc)
        
@@ -372,7 +372,7 @@ Source code:
        w2 :: Foo T
        w2 = MkFoo (\(MkT x) -> case w1 of MkFoo f -> f x)
 
-After desugaring, and discading the data constructors for the newtypes,
+After desugaring, and discarding the data constructors for the newtypes,
 we get:
        w2 :: Foo T
        w2 = w1
@@ -455,19 +455,22 @@ data PrimRep
   | AddrRep            -- a pointer, but not to a Haskell value
   | FloatRep
   | DoubleRep
-  deriving( Eq )
-
--- Size of a PrimRep, in bytes
-sizeofPrimRep :: PrimRep -> Int
-sizeofPrimRep IntRep   = wORD_SIZE
-sizeofPrimRep WordRep  = wORD_SIZE
-sizeofPrimRep Int64Rep = wORD64_SIZE
-sizeofPrimRep Word64Rep= wORD64_SIZE
-sizeofPrimRep FloatRep = 4
-sizeofPrimRep DoubleRep= 8
-sizeofPrimRep AddrRep  = wORD_SIZE
-sizeofPrimRep PtrRep   = wORD_SIZE
-sizeofPrimRep VoidRep  = 0
+  deriving( Eq, Show )
+
+instance Outputable PrimRep where
+  ppr r = text (show r)
+
+-- Size of a PrimRep, in words
+primRepSizeW :: PrimRep -> Int
+primRepSizeW IntRep   = 1
+primRepSizeW WordRep  = 1
+primRepSizeW Int64Rep = wORD64_SIZE `quot` wORD_SIZE
+primRepSizeW Word64Rep= wORD64_SIZE `quot` wORD_SIZE
+primRepSizeW FloatRep = 1    -- NB. might not take a full word
+primRepSizeW DoubleRep= dOUBLE_SIZE `quot` wORD_SIZE
+primRepSizeW AddrRep  = 1
+primRepSizeW PtrRep   = 1
+primRepSizeW VoidRep  = 0
 \end{code}
 
 %************************************************************************
@@ -929,14 +932,14 @@ synTyConResKind tycon  = pprPanic "synTyConResKind" (ppr tycon)
 \end{code}
 
 \begin{code}
-maybeTyConSingleCon :: TyCon -> Maybe DataCon
-maybeTyConSingleCon (AlgTyCon {algTcRhs = DataTyCon {data_cons = [c] }}) = Just c
-maybeTyConSingleCon (AlgTyCon {algTcRhs = NewTyCon { data_con = c }})    = Just c
-maybeTyConSingleCon (AlgTyCon {})               = Nothing
-maybeTyConSingleCon (TupleTyCon {dataCon = con}) = Just con
-maybeTyConSingleCon (PrimTyCon {})               = Nothing
-maybeTyConSingleCon (FunTyCon {})                = Nothing  -- case at funty
-maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
+tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon
+tyConSingleDataCon_maybe (AlgTyCon {algTcRhs = DataTyCon {data_cons = [c] }}) = Just c
+tyConSingleDataCon_maybe (AlgTyCon {algTcRhs = NewTyCon { data_con = c }})    = Just c
+tyConSingleDataCon_maybe (AlgTyCon {})          = Nothing
+tyConSingleDataCon_maybe (TupleTyCon {dataCon = con}) = Just con
+tyConSingleDataCon_maybe (PrimTyCon {})               = Nothing
+tyConSingleDataCon_maybe (FunTyCon {})                = Nothing  -- case at funty
+tyConSingleDataCon_maybe tc = pprPanic "tyConSingleDataCon_maybe: unexpected tycon " $ ppr tc
 \end{code}
 
 \begin{code}