ext-core library: Export a lot more things from Prims
[ghc-hetmet.git] / utils / ext-core / Language / Core / Prims.hs
1 {-# OPTIONS -Wall #-}
2
3 {- This module contains a few primitive types that need to be wired in.
4    Most are defined in PrimEnv, which is automatically generated from
5    GHC's primops.txt. -}
6
7 module Language.Core.Prims(initialEnv, primEnv, primId, bv,
8              tIntzh, tInt64zh, tCharzh, tFloatzh, tAddrzh, tDoublezh, tcStatezh,
9              tWordzh, tWord64zh, tByteArrayzh,
10              tcStablePtrzh, tcIO, mkInitialEnv, mkTypeEnv, tRWS, tBool,
11              ioBaseMname) where
12
13 import Control.Monad
14
15 import Language.Core.Core
16 import Language.Core.Encoding
17 import Language.Core.Env
18 import Language.Core.Check
19 import Language.Core.PrimCoercions
20 import Language.Core.PrimEnv
21
22 initialEnv :: Menv
23 initialEnv = efromlist [(primMname,primEnv),
24                      (errMname,errorEnv),
25                      (boolMname,boolEnv)]
26
27 primEnv :: Envs
28 -- Tediously, we add defs for ByteArray# etc. because these are
29 -- declared as ByteArr# (etc.) in primops.txt, and GHC has
30 -- ByteArray# etc. wired-in.
31 -- At least this is better than when all primops were wired-in here.
32 primEnv = Envs {tcenv_=efromlist $ map (\ (t,k) -> (t,Kind k)) $ 
33                   [(snd tcByteArrayzh,ktByteArrayzh), 
34                    (snd tcMutableArrayzh, ktMutableArrayzh),
35                    (snd tcMutableByteArrayzh, ktMutableByteArrayzh)] ++
36                  ([(snd $ tcUtuple n, ktUtuple n) | n <- [1..maxUtuple]] 
37                    ++ ((snd tcArrow,ktArrow):primTcs)),
38                 cenv_=efromlist primDcs,
39                 venv_=efromlist (opsState ++ primVals)}
40
41 errorEnv :: Envs
42 errorEnv = Envs {tcenv_=eempty,
43                  cenv_=eempty,
44                  venv_=efromlist errorVals}
45
46 -- Unpleasantly, we wire in the Bool type because some people
47 -- (i.e. me) need to depend on it being primitive. This shouldn't
48 -- hurt anything, since if someone pulls in the GHC.Bool module,
49 -- it will override this definition.
50 boolEnv :: Envs
51 boolEnv = Envs {tcenv_=efromlist boolTcs,
52                 cenv_=efromlist boolDcs,
53                 venv_=eempty}
54
55 boolTcs :: [(Tcon, KindOrCoercion)]
56 boolTcs = [(snd tcBool, Kind Klifted)]
57             
58 boolDcs :: [(Dcon, Ty)]
59 boolDcs = [(dcTrue, tBool),
60            (dcFalse, tBool)]
61
62 primDcs :: [(Dcon,Ty)]
63 primDcs = map (\ ((_,c),t) -> (c,t))
64               [(dcUtuple n, dcUtupleTy n) | n <- [1..maxUtuple]]
65
66 tRWS :: Ty
67 tRWS = tStatezh tRealWorld
68
69 opsState :: [(Var, Ty)]
70 opsState = [
71   ("realWorldzh", tRWS)]
72
73 {- Arrays -}
74
75 tcByteArrayzh, tcMutableArrayzh, tcMutableByteArrayzh :: Qual Tcon
76 ktByteArrayzh, ktMutableArrayzh, ktMutableByteArrayzh :: Kind
77
78 tcByteArrayzh = pvz "ByteArray"
79 ktByteArrayzh = Kunlifted
80
81 tcMutableArrayzh = pvz "MutableArray"
82 ktMutableArrayzh = Karrow Klifted (Karrow Klifted Kunlifted)
83
84 tcMutableByteArrayzh = pvz "MutableByteArray"
85 ktMutableByteArrayzh = Karrow Klifted Kunlifted
86
87 {- Real world and state. -}
88
89 -- tjc: why isn't this one unboxed?
90 tcRealWorld :: Qual Tcon
91 tcRealWorld = pv "RealWorld"
92 tRealWorld :: Ty
93 tRealWorld = Tcon tcRealWorld
94
95 tcStatezh :: Qual Tcon
96 tcStatezh = pvz "State"
97 tStatezh :: Ty -> Ty
98 tStatezh t = Tapp (Tcon tcStatezh) t
99
100 {- Properly defined in PrelError, but needed in many modules before that. -}
101 errorVals :: [(Var, Ty)]
102 errorVals = [
103  ("error", Tforall ("a",Kopen) (tArrow tString (Tvar "a"))),
104  ("irrefutPatError", str2A),
105  ("patError", str2A),
106  ("divZZeroError", forallAA),
107  ("overflowError", forallAA)]
108
109 {- Non-primitive, but mentioned in the types of primitives. -}
110
111 bv :: a -> Qual a
112 bv = qual baseMname
113
114 str2A, forallAA :: Ty  
115 str2A = Tforall ("a",Kopen) (tArrow tAddrzh (Tvar "a"))
116 forallAA = Tforall ("a",Kopen) (Tvar "a")
117
118 tBool :: Ty
119 tBool = Tcon tcBool
120 tcBool :: Qual Tcon
121 tcBool = (Just boolMname, "Bool")
122 tcChar :: Qual Tcon
123 tcChar = bv "Char"
124 tChar :: Ty
125 tChar = Tcon tcChar
126 tcList :: Qual Tcon
127 tcList = bv "ZMZN"
128 tList :: Ty -> Ty
129 tList t = Tapp (Tcon tcList) t
130 tString :: Ty
131 tString = tList tChar
132 tIntzh, tInt64zh, tWordzh, tWord64zh, tCharzh, tFloatzh, tDoublezh, {-tIOUnit,-} 
133   tByteArrayzh :: Ty
134 tIntzh = Tcon (primId "Int#")
135 tInt64zh = Tcon (primId "Int64#")
136 tWordzh = Tcon (primId "Word#")
137 tWord64zh = Tcon (primId "Word64#")
138 tByteArrayzh = Tcon (primId "ByteArray#")
139 tCharzh = Tcon (primId "Char#")
140 tFloatzh = Tcon (primId "Float#")
141 tDoublezh = Tcon (primId "Double#")
142 tcStablePtrzh, tcIO :: Qual Tcon
143 tcStablePtrzh = pvz "StablePtr"
144 tcIO = (Just (mkBaseMname "IOBase"), "IO")
145
146 primId :: String -> Qual Id
147 primId = pv . zEncodeString
148
149 --- doesn't really belong here... sigh
150
151 mkInitialEnv :: [Module] -> IO Menv
152 mkInitialEnv libs = foldM mkTypeEnv initialEnv libs
153                     
154 mkTypeEnv :: Menv -> Module -> IO Menv
155 mkTypeEnv globalEnv m@(Module mn _ _) = 
156     catch (return (envsModule globalEnv m)) handler
157         where handler e = do
158                 putStrLn ("WARNING: mkTypeEnv caught an exception " ++ show e 
159                                     ++ " while processing " ++ show mn)
160                 return globalEnv
161
162 ----- move this 
163 ioBaseMname :: AnMname
164 ioBaseMname = mkBaseMname "IOBase"