X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=utils%2Fext-core%2FCore.hs;h=9df300e010a3519522f4d2e9e2fe523149a59275;hb=41ba0887070487f5cb0f60c55e8f612a6bcaccff;hp=66270cd36ca43b0ce3ff319966c90a23f2e2d056;hpb=10704b34c1928dde3d0ef33fe37c3eb7b948975f;p=ghc-hetmet.git diff --git a/utils/ext-core/Core.hs b/utils/ext-core/Core.hs index 66270cd..9df300e 100644 --- a/utils/ext-core/Core.hs +++ b/utils/ext-core/Core.hs @@ -2,26 +2,33 @@ module Core where import Encoding +import Data.Generics import List (elemIndex) data Module = Module AnMname [Tdef] [Vdefg] + deriving (Data, Typeable) data Tdef = Data (Qual Tcon) [Tbind] [Cdef] - | Newtype (Qual Tcon) [Tbind] Axiom (Maybe Ty) + -- type constructor; coercion name; type arguments; type rep + -- If we have: (Newtype tc co tbs (Just t)) + -- there is an implicit axiom: + -- co tbs :: tc tbs :=: t + | Newtype (Qual Tcon) (Qual Tcon) [Tbind] (Maybe Ty) + deriving (Data, Typeable) data Cdef = Constr (Qual Dcon) [Tbind] [Ty] - --- Newtype coercion -type Axiom = (Qual Tcon, [Tbind], (Ty,Ty)) + deriving (Data, Typeable) data Vdefg = Rec [Vdef] | Nonrec Vdef + deriving (Data, Typeable) newtype Vdef = Vdef (Qual Var,Ty,Exp) + deriving (Data, Typeable) data Exp = Var (Qual Var) @@ -35,15 +42,18 @@ data Exp | Cast Exp Ty | Note String Exp | External String Ty + deriving (Data, Typeable) data Bind = Vb Vbind | Tb Tbind + deriving (Data, Typeable) data Alt = Acon (Qual Dcon) [Tbind] [Vbind] Exp | Alit Lit Exp | Adefault Exp + deriving (Data, Typeable) type Vbind = (Var,Ty) type Tbind = (Tvar,Kind) @@ -63,6 +73,7 @@ data Ty | InstCoercion Ty Ty | LeftCoercion Ty | RightCoercion Ty + deriving (Data, Typeable) data Kind = Klifted @@ -70,6 +81,7 @@ data Kind | Kopen | Karrow Kind Kind | Keq Ty Ty + deriving (Data, Typeable) -- A CoercionKind isn't really a Kind at all, but rather, -- corresponds to an arbitrary user-declared axiom. @@ -91,13 +103,13 @@ data CoercionKind = data KindOrCoercion = Kind Kind | Coercion CoercionKind data Lit = Literal CoreLit Ty - deriving Eq -- with nearlyEqualTy + deriving (Data, Typeable, Eq) -- with nearlyEqualTy data CoreLit = Lint Integer | Lrational Rational | Lchar Char | Lstring String - deriving Eq + deriving (Data, Typeable, Eq) -- Right now we represent module names as triples: -- (package name, hierarchical names, leaf name) @@ -110,8 +122,9 @@ data CoreLit = Lint Integer type Mname = Maybe AnMname newtype AnMname = M (Pname, [Id], Id) - deriving (Eq, Ord) -type Pname = Id + deriving (Eq, Ord, Data, Typeable) +newtype Pname = P Id + deriving (Eq, Ord, Data, Typeable) type Var = Id type Tvar = Id type Tcon = Id @@ -125,6 +138,9 @@ qual mn t = (Just mn, t) unqual :: t -> Qual t unqual = (,) Nothing +getModule :: Qual t -> Mname +getModule = fst + type Id = String eqKind :: Kind -> Kind -> Bool @@ -183,16 +199,23 @@ errMname = mkBaseMname "Err" mkBaseMname,mkPrimMname :: Id -> AnMname mkBaseMname mn = M (basePkg, ghcPrefix, mn) mkPrimMname mn = M (primPkg, ghcPrefix, mn) -basePkg = "base" -mainPkg = "main" -primPkg = zEncodeString "ghc-prim" +basePkg = P "base" +mainPkg = P "main" +primPkg = P $ zEncodeString "ghc-prim" ghcPrefix = ["GHC"] mainPrefix = [] baseMname = mkBaseMname "Base" boolMname = mkPrimMname "Bool" mainVar = qual mainMname "main" +wrapperMainVar = qual wrapperMainMname "main" mainMname = M (mainPkg, mainPrefix, "Main") -wrapperMainMname = Just $ M (mainPkg, mainPrefix, "ZCMain") +wrapperMainMname = M (mainPkg, mainPrefix, "ZCMain") +wrapperMainAnMname = Just wrapperMainMname + +dcTrue :: Dcon +dcTrue = "True" +dcFalse :: Dcon +dcFalse = "False" tcArrow :: Qual Tcon tcArrow = (Just primMname, "ZLzmzgZR") @@ -200,6 +223,9 @@ tcArrow = (Just primMname, "ZLzmzgZR") tArrow :: Ty -> Ty -> Ty tArrow t1 t2 = Tapp (Tapp (Tcon tcArrow) t1) t2 +mkFunTy :: Ty -> Ty -> Ty +mkFunTy randTy resultTy = + Tapp (Tapp (Tcon tcArrow) randTy) resultTy ktArrow :: Kind ktArrow = Karrow Kopen (Karrow Kopen Klifted) @@ -242,4 +268,8 @@ dcUtupleTy n = utuple :: [Ty] -> [Exp] -> Exp utuple ts es = foldl App (foldl Appt (Dcon (dcUtuple (length es))) ts) es - +---- snarfed from GHC's CoreSyn +flattenBinds :: [Vdefg] -> [Vdef] -- Get all the lhs/rhs pairs +flattenBinds (Nonrec vd : binds) = vd : flattenBinds binds +flattenBinds (Rec prs1 : binds) = prs1 ++ flattenBinds binds +flattenBinds [] = []