NCG: Validate fixes for powerpc
[ghc-hetmet.git] / compiler / nativeGen / X86 / Regs.hs
1 module X86.Regs (
2
3         -- sizes
4         Size(..),
5         intSize, 
6         floatSize, 
7         isFloatSize, 
8         wordSize,
9         cmmTypeSize,
10         sizeToWidth,
11         mkVReg,
12
13         -- immediates
14         Imm(..),
15         strImmLit,
16         litToImm,
17
18         -- addressing modes
19         AddrMode(..),
20         addrOffset,
21
22         -- registers
23         spRel,
24         argRegs,
25         allArgRegs,
26         callClobberedRegs,
27         allMachRegNos,
28         regClass,
29         showReg,        
30
31         -- machine specific
32         EABase(..), EAIndex(..), addrModeRegs,
33
34         eax, ebx, ecx, edx, esi, edi, ebp, esp,
35         fake0, fake1, fake2, fake3, fake4, fake5,
36
37         rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
38         r8,  r9,  r10, r11, r12, r13, r14, r15,
39         xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
40         xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15,
41         xmm,
42
43         ripRel,
44         allFPArgRegs,
45
46         -- horror show
47         freeReg,
48         globalRegMaybe
49 )
50
51 where
52
53 #include "nativeGen/NCG.h"
54 #include "HsVersions.h"
55
56 #if i386_TARGET_ARCH
57 # define STOLEN_X86_REGS 4
58 -- HACK: go for the max
59 #endif
60
61 #include "../includes/MachRegs.h"
62
63 import RegsBase
64
65 import BlockId
66 import Cmm
67 import CLabel           ( CLabel )
68 import Pretty
69 import Outputable       ( Outputable(..), pprPanic, panic )
70 import qualified Outputable
71 import Unique
72 import FastBool
73
74 #if  defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
75 import Constants
76 #endif
77
78 -- -----------------------------------------------------------------------------
79 -- Sizes on this architecture
80 -- 
81 -- A Size is usually a combination of width and class
82
83 -- It looks very like the old MachRep, but it's now of purely local
84 -- significance, here in the native code generator.  You can change it
85 -- without global consequences.
86 --
87 -- A major use is as an opcode qualifier; thus the opcode 
88 --      mov.l a b
89 -- might be encoded 
90 --      MOV II32 a b
91 -- where the Size field encodes the ".l" part.
92
93 -- ToDo: it's not clear to me that we need separate signed-vs-unsigned sizes
94 -- here.  I've removed them from the x86 version, we'll see what happens --SDM
95
96 -- ToDo: quite a few occurrences of Size could usefully be replaced by Width
97
98 data Size
99         = II8 | II16 | II32 | II64 | FF32 | FF64 | FF80
100         deriving Eq
101
102 intSize, floatSize :: Width -> Size
103 intSize W8 = II8
104 intSize W16 = II16
105 intSize W32 = II32
106 intSize W64 = II64
107 intSize other = pprPanic "MachInstrs.intSize" (ppr other)
108
109
110 floatSize W32 = FF32
111 floatSize W64 = FF64
112 floatSize other = pprPanic "MachInstrs.intSize" (ppr other)
113
114
115 isFloatSize :: Size -> Bool
116 isFloatSize FF32 = True
117 isFloatSize FF64 = True
118 isFloatSize FF80 = True
119 isFloatSize _    = False
120
121
122 wordSize :: Size
123 wordSize = intSize wordWidth
124
125
126 cmmTypeSize :: CmmType -> Size
127 cmmTypeSize ty | isFloatType ty = floatSize (typeWidth ty)
128                | otherwise      = intSize (typeWidth ty)
129
130
131 sizeToWidth :: Size -> Width
132 sizeToWidth II8  = W8
133 sizeToWidth II16 = W16
134 sizeToWidth II32 = W32
135 sizeToWidth II64 = W64
136 sizeToWidth FF32 = W32
137 sizeToWidth FF64 = W64
138 sizeToWidth _ = panic "MachInstrs.sizeToWidth"
139
140
141 mkVReg :: Unique -> Size -> Reg
142 mkVReg u size
143    | not (isFloatSize size) = VirtualRegI u
144    | otherwise
145    = case size of
146         FF32    -> VirtualRegD u
147         FF64    -> VirtualRegD u
148         _       -> panic "mkVReg"
149
150
151 -- -----------------------------------------------------------------------------
152 -- Immediates
153
154 data Imm
155   = ImmInt      Int
156   | ImmInteger  Integer     -- Sigh.
157   | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
158   | ImmLit      Doc         -- Simple string
159   | ImmIndex    CLabel Int
160   | ImmFloat    Rational
161   | ImmDouble   Rational
162   | ImmConstantSum Imm Imm
163   | ImmConstantDiff Imm Imm
164
165
166 strImmLit :: String -> Imm
167 strImmLit s = ImmLit (text s)
168
169
170 litToImm :: CmmLit -> Imm
171 litToImm (CmmInt i w)        = ImmInteger (narrowS w i)
172                 -- narrow to the width: a CmmInt might be out of
173                 -- range, but we assume that ImmInteger only contains
174                 -- in-range values.  A signed value should be fine here.
175 litToImm (CmmFloat f W32)    = ImmFloat f
176 litToImm (CmmFloat f W64)    = ImmDouble f
177 litToImm (CmmLabel l)        = ImmCLbl l
178 litToImm (CmmLabelOff l off) = ImmIndex l off
179 litToImm (CmmLabelDiffOff l1 l2 off)
180                              = ImmConstantSum
181                                (ImmConstantDiff (ImmCLbl l1) (ImmCLbl l2))
182                                (ImmInt off)
183 litToImm (CmmBlock id)       = ImmCLbl (infoTblLbl id)
184 litToImm _                   = panic "X86.Regs.litToImm: no match"
185
186 -- addressing modes ------------------------------------------------------------
187
188 data AddrMode
189         = AddrBaseIndex EABase EAIndex Displacement
190         | ImmAddr Imm Int
191
192 data EABase       = EABaseNone  | EABaseReg Reg | EABaseRip
193 data EAIndex      = EAIndexNone | EAIndex Reg Int
194 type Displacement = Imm
195
196
197 addrOffset :: AddrMode -> Int -> Maybe AddrMode
198 addrOffset addr off
199   = case addr of
200       ImmAddr i off0      -> Just (ImmAddr i (off0 + off))
201
202       AddrBaseIndex r i (ImmInt n) -> Just (AddrBaseIndex r i (ImmInt (n + off)))
203       AddrBaseIndex r i (ImmInteger n)
204         -> Just (AddrBaseIndex r i (ImmInt (fromInteger (n + toInteger off))))
205
206       AddrBaseIndex r i (ImmCLbl lbl)
207         -> Just (AddrBaseIndex r i (ImmIndex lbl off))
208
209       AddrBaseIndex r i (ImmIndex lbl ix)
210         -> Just (AddrBaseIndex r i (ImmIndex lbl (ix+off)))
211
212       _ -> Nothing  -- in theory, shouldn't happen
213
214
215 addrModeRegs :: AddrMode -> [Reg]
216 addrModeRegs (AddrBaseIndex b i _) =  b_regs ++ i_regs
217   where
218    b_regs = case b of { EABaseReg r -> [r]; _ -> [] }
219    i_regs = case i of { EAIndex r _ -> [r]; _ -> [] }
220 addrModeRegs _ = []
221
222
223 -- registers -------------------------------------------------------------------
224
225 -- @spRel@ gives us a stack relative addressing mode for volatile
226 -- temporaries and for excess call arguments.  @fpRel@, where
227 -- applicable, is the same but for the frame pointer.
228
229
230 spRel :: Int            -- ^ desired stack offset in words, positive or negative
231       -> AddrMode
232
233 #if   i386_TARGET_ARCH
234 spRel n = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt (n * wORD_SIZE))
235
236 #elif x86_64_TARGET_ARCH
237 spRel n = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt (n * wORD_SIZE))
238
239 #else
240 spRel _ = panic "X86.Regs.spRel: not defined for this architecture"
241
242 #endif
243
244
245 -- argRegs is the set of regs which are read for an n-argument call to C.
246 -- For archs which pass all args on the stack (x86), is empty.
247 -- Sparc passes up to the first 6 args in regs.
248 -- Dunno about Alpha.
249 argRegs :: RegNo -> [Reg]
250 argRegs _       = panic "MachRegs.argRegs(x86): should not be used!"
251
252
253
254
255
256 -- | The complete set of machine registers.
257 allMachRegNos :: [RegNo]
258
259 #if   i386_TARGET_ARCH
260 allMachRegNos   = [0..13]
261
262 #elif x86_64_TARGET_ARCH
263 allMachRegNos  = [0..31]
264
265 #else
266 allMachRegNos   = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
267
268 #endif
269
270
271 -- | Take the class of a register.
272 {-# INLINE regClass      #-}
273 regClass :: Reg -> RegClass
274
275 #if   i386_TARGET_ARCH
276 -- On x86, we might want to have an 8-bit RegClass, which would
277 -- contain just regs 1-4 (the others don't have 8-bit versions).
278 -- However, we can get away without this at the moment because the
279 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
280 regClass (RealReg i)     = if i < 8 then RcInteger else RcDouble
281 regClass (VirtualRegI  _) = RcInteger
282 regClass (VirtualRegHi _) = RcInteger
283 regClass (VirtualRegD  _) = RcDouble
284 regClass (VirtualRegF  u) = pprPanic ("regClass(x86):VirtualRegF") (ppr u)
285
286 #elif x86_64_TARGET_ARCH
287 -- On x86, we might want to have an 8-bit RegClass, which would
288 -- contain just regs 1-4 (the others don't have 8-bit versions).
289 -- However, we can get away without this at the moment because the
290 -- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
291 regClass (RealReg i)     = if i < 16 then RcInteger else RcDouble
292 regClass (VirtualRegI  _) = RcInteger
293 regClass (VirtualRegHi _) = RcInteger
294 regClass (VirtualRegD  _) = RcDouble
295 regClass (VirtualRegF  u) = pprPanic "regClass(x86_64):VirtualRegF" (ppr u)
296
297 #else
298 regClass _      = panic "X86.Regs.regClass: not defined for this architecture"
299
300 #endif
301
302
303 -- | Get the name of the register with this number.
304 showReg :: RegNo -> String
305
306 #if   i386_TARGET_ARCH
307 showReg n
308    = if   n >= 0 && n < 14
309      then regNames !! n
310      else "%unknown_x86_real_reg_" ++ show n
311
312 regNames :: [String]
313 regNames 
314    = ["%eax", "%ebx", "%ecx", "%edx", "%esi", "%edi", "%ebp", "%esp", 
315       "%fake0", "%fake1", "%fake2", "%fake3", "%fake4", "%fake5", "%fake6"]
316
317 #elif x86_64_TARGET_ARCH
318 showReg n
319         | n >= 16       = "%xmm" ++ show (n-16)
320         | n >= 8        = "%r" ++ show n
321         | otherwise     = regNames !! n
322
323 regNames :: [String]
324 regNames 
325  = ["%rax", "%rbx", "%rcx", "%rdx", "%rsi", "%rdi", "%rbp", "%rsp" ]
326
327 #else
328 showReg _       = panic "X86.Regs.showReg: not defined for this architecture"
329
330 #endif
331
332
333
334
335 -- machine specific ------------------------------------------------------------
336
337
338 {-
339 Intel x86 architecture:
340 - All registers except 7 (esp) are available for use.
341 - Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
342 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
343 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
344 - Registers 8-13 are fakes; we pretend x86 has 6 conventionally-addressable
345   fp registers, and 3-operand insns for them, and we translate this into
346   real stack-based x86 fp code after register allocation.
347
348 The fp registers are all Double registers; we don't have any RcFloat class
349 regs.  @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
350 never generate them.
351 -}
352
353 fake0, fake1, fake2, fake3, fake4, fake5, 
354        eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg
355
356 eax   = RealReg 0
357 ebx   = RealReg 1
358 ecx   = RealReg 2
359 edx   = RealReg 3
360 esi   = RealReg 4
361 edi   = RealReg 5
362 ebp   = RealReg 6
363 esp   = RealReg 7
364 fake0 = RealReg 8
365 fake1 = RealReg 9
366 fake2 = RealReg 10
367 fake3 = RealReg 11
368 fake4 = RealReg 12
369 fake5 = RealReg 13
370
371
372
373 {-
374 AMD x86_64 architecture:
375 - Registers 0-16 have 32-bit counterparts (eax, ebx etc.)
376 - Registers 0-7 have 16-bit counterparts (ax, bx etc.)
377 - Registers 0-3 have 8 bit counterparts (ah, bh etc.)
378
379 -}
380
381 rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi, 
382   r8, r9, r10, r11, r12, r13, r14, r15,
383   xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
384   xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg
385
386 rax   = RealReg 0
387 rbx   = RealReg 1
388 rcx   = RealReg 2
389 rdx   = RealReg 3
390 rsi   = RealReg 4
391 rdi   = RealReg 5
392 rbp   = RealReg 6
393 rsp   = RealReg 7
394 r8    = RealReg 8
395 r9    = RealReg 9
396 r10   = RealReg 10
397 r11   = RealReg 11
398 r12   = RealReg 12
399 r13   = RealReg 13
400 r14   = RealReg 14
401 r15   = RealReg 15
402 xmm0  = RealReg 16
403 xmm1  = RealReg 17
404 xmm2  = RealReg 18
405 xmm3  = RealReg 19
406 xmm4  = RealReg 20
407 xmm5  = RealReg 21
408 xmm6  = RealReg 22
409 xmm7  = RealReg 23
410 xmm8  = RealReg 24
411 xmm9  = RealReg 25
412 xmm10 = RealReg 26
413 xmm11 = RealReg 27
414 xmm12 = RealReg 28
415 xmm13 = RealReg 29
416 xmm14 = RealReg 30
417 xmm15 = RealReg 31
418
419 allFPArgRegs :: [Reg]
420 allFPArgRegs    = map RealReg [16 .. 23]
421
422 ripRel :: Displacement -> AddrMode
423 ripRel imm      = AddrBaseIndex EABaseRip EAIndexNone imm
424
425
426  -- so we can re-use some x86 code:
427 {-
428 eax = rax
429 ebx = rbx
430 ecx = rcx
431 edx = rdx
432 esi = rsi
433 edi = rdi
434 ebp = rbp
435 esp = rsp
436 -}
437
438 xmm :: RegNo -> Reg
439 xmm n = RealReg (16+n)
440
441
442
443
444 -- horror show -----------------------------------------------------------------
445 freeReg                 :: RegNo -> FastBool
446 globalRegMaybe          :: GlobalReg -> Maybe Reg
447 allArgRegs              :: [Reg]
448 callClobberedRegs       :: [Reg]
449
450 #if defined(i386_TARGET_ARCH) || defined(x86_64_TARGET_ARCH)
451
452 #if i386_TARGET_ARCH
453 #define eax 0
454 #define ebx 1
455 #define ecx 2
456 #define edx 3
457 #define esi 4
458 #define edi 5
459 #define ebp 6
460 #define esp 7
461 #define fake0 8
462 #define fake1 9
463 #define fake2 10
464 #define fake3 11
465 #define fake4 12
466 #define fake5 13
467 #endif
468
469 #if x86_64_TARGET_ARCH
470 #define rax   0
471 #define rbx   1
472 #define rcx   2
473 #define rdx   3
474 #define rsi   4
475 #define rdi   5
476 #define rbp   6
477 #define rsp   7
478 #define r8    8
479 #define r9    9
480 #define r10   10
481 #define r11   11
482 #define r12   12
483 #define r13   13
484 #define r14   14
485 #define r15   15
486 #define xmm0  16
487 #define xmm1  17
488 #define xmm2  18
489 #define xmm3  19
490 #define xmm4  20
491 #define xmm5  21
492 #define xmm6  22
493 #define xmm7  23
494 #define xmm8  24
495 #define xmm9  25
496 #define xmm10 26
497 #define xmm11 27
498 #define xmm12 28
499 #define xmm13 29
500 #define xmm14 30
501 #define xmm15 31
502 #endif
503
504
505
506 #if i386_TARGET_ARCH
507 freeReg esp = fastBool False  --        %esp is the C stack pointer
508 #endif
509
510 #if x86_64_TARGET_ARCH
511 freeReg rsp = fastBool False  --        %rsp is the C stack pointer
512 #endif
513
514 #ifdef REG_Base
515 freeReg REG_Base = fastBool False
516 #endif
517 #ifdef REG_R1
518 freeReg REG_R1   = fastBool False
519 #endif  
520 #ifdef REG_R2  
521 freeReg REG_R2   = fastBool False
522 #endif  
523 #ifdef REG_R3  
524 freeReg REG_R3   = fastBool False
525 #endif  
526 #ifdef REG_R4  
527 freeReg REG_R4   = fastBool False
528 #endif  
529 #ifdef REG_R5  
530 freeReg REG_R5   = fastBool False
531 #endif  
532 #ifdef REG_R6  
533 freeReg REG_R6   = fastBool False
534 #endif  
535 #ifdef REG_R7  
536 freeReg REG_R7   = fastBool False
537 #endif  
538 #ifdef REG_R8  
539 freeReg REG_R8   = fastBool False
540 #endif
541 #ifdef REG_F1
542 freeReg REG_F1 = fastBool False
543 #endif
544 #ifdef REG_F2
545 freeReg REG_F2 = fastBool False
546 #endif
547 #ifdef REG_F3
548 freeReg REG_F3 = fastBool False
549 #endif
550 #ifdef REG_F4
551 freeReg REG_F4 = fastBool False
552 #endif
553 #ifdef REG_D1
554 freeReg REG_D1 = fastBool False
555 #endif
556 #ifdef REG_D2
557 freeReg REG_D2 = fastBool False
558 #endif
559 #ifdef REG_Sp 
560 freeReg REG_Sp   = fastBool False
561 #endif 
562 #ifdef REG_Su
563 freeReg REG_Su   = fastBool False
564 #endif 
565 #ifdef REG_SpLim 
566 freeReg REG_SpLim = fastBool False
567 #endif 
568 #ifdef REG_Hp 
569 freeReg REG_Hp   = fastBool False
570 #endif
571 #ifdef REG_HpLim
572 freeReg REG_HpLim = fastBool False
573 #endif
574 freeReg _               = fastBool True
575
576
577 --  | Returns 'Nothing' if this global register is not stored
578 -- in a real machine register, otherwise returns @'Just' reg@, where
579 -- reg is the machine register it is stored in.
580
581 #ifdef REG_Base
582 globalRegMaybe BaseReg                  = Just (RealReg REG_Base)
583 #endif
584 #ifdef REG_R1
585 globalRegMaybe (VanillaReg 1 _)         = Just (RealReg REG_R1)
586 #endif 
587 #ifdef REG_R2 
588 globalRegMaybe (VanillaReg 2 _)         = Just (RealReg REG_R2)
589 #endif 
590 #ifdef REG_R3 
591 globalRegMaybe (VanillaReg 3 _)         = Just (RealReg REG_R3)
592 #endif 
593 #ifdef REG_R4 
594 globalRegMaybe (VanillaReg 4 _)         = Just (RealReg REG_R4)
595 #endif 
596 #ifdef REG_R5 
597 globalRegMaybe (VanillaReg 5 _)         = Just (RealReg REG_R5)
598 #endif 
599 #ifdef REG_R6 
600 globalRegMaybe (VanillaReg 6 _)         = Just (RealReg REG_R6)
601 #endif 
602 #ifdef REG_R7 
603 globalRegMaybe (VanillaReg 7 _)         = Just (RealReg REG_R7)
604 #endif 
605 #ifdef REG_R8 
606 globalRegMaybe (VanillaReg 8 _)         = Just (RealReg REG_R8)
607 #endif
608 #ifdef REG_R9 
609 globalRegMaybe (VanillaReg 9 _)         = Just (RealReg REG_R9)
610 #endif
611 #ifdef REG_R10 
612 globalRegMaybe (VanillaReg 10 _)        = Just (RealReg REG_R10)
613 #endif
614 #ifdef REG_F1
615 globalRegMaybe (FloatReg 1)             = Just (RealReg REG_F1)
616 #endif                                  
617 #ifdef REG_F2                           
618 globalRegMaybe (FloatReg 2)             = Just (RealReg REG_F2)
619 #endif                                  
620 #ifdef REG_F3                           
621 globalRegMaybe (FloatReg 3)             = Just (RealReg REG_F3)
622 #endif                                  
623 #ifdef REG_F4                           
624 globalRegMaybe (FloatReg 4)             = Just (RealReg REG_F4)
625 #endif                                  
626 #ifdef REG_D1                           
627 globalRegMaybe (DoubleReg 1)            = Just (RealReg REG_D1)
628 #endif                                  
629 #ifdef REG_D2                           
630 globalRegMaybe (DoubleReg 2)            = Just (RealReg REG_D2)
631 #endif
632 #ifdef REG_Sp       
633 globalRegMaybe Sp                       = Just (RealReg REG_Sp)
634 #endif
635 #ifdef REG_Lng1                         
636 globalRegMaybe (LongReg 1)              = Just (RealReg REG_Lng1)
637 #endif                                  
638 #ifdef REG_Lng2                         
639 globalRegMaybe (LongReg 2)              = Just (RealReg REG_Lng2)
640 #endif
641 #ifdef REG_SpLim                                
642 globalRegMaybe SpLim                    = Just (RealReg REG_SpLim)
643 #endif                                  
644 #ifdef REG_Hp                           
645 globalRegMaybe Hp                       = Just (RealReg REG_Hp)
646 #endif                                  
647 #ifdef REG_HpLim                        
648 globalRegMaybe HpLim                    = Just (RealReg REG_HpLim)
649 #endif                                  
650 #ifdef REG_CurrentTSO                           
651 globalRegMaybe CurrentTSO               = Just (RealReg REG_CurrentTSO)
652 #endif                                  
653 #ifdef REG_CurrentNursery                       
654 globalRegMaybe CurrentNursery           = Just (RealReg REG_CurrentNursery)
655 #endif                                  
656 globalRegMaybe _                        = Nothing
657
658 -- 
659
660 #if   i386_TARGET_ARCH
661 allArgRegs = panic "X86.Regs.allArgRegs: should not be used!"
662
663 #elif x86_64_TARGET_ARCH
664 allArgRegs = map RealReg [rdi,rsi,rdx,rcx,r8,r9]
665
666 #else
667 allArgRegs  = panic "X86.Regs.allArgRegs: not defined for this architecture"
668 #endif
669
670
671 -- | these are the regs which we cannot assume stay alive over a C call.  
672
673 #if   i386_TARGET_ARCH
674 -- caller-saves registers
675 callClobberedRegs
676   = map RealReg [eax,ecx,edx,fake0,fake1,fake2,fake3,fake4,fake5]
677
678 #elif x86_64_TARGET_ARCH
679 -- all xmm regs are caller-saves
680 -- caller-saves registers
681 callClobberedRegs    
682   = map RealReg ([rax,rcx,rdx,rsi,rdi,r8,r9,r10,r11] ++ [16..31])
683
684 #else
685 callClobberedRegs
686   = panic "X86.Regs.callClobberedRegs: not defined for this architecture"
687 #endif
688
689 #else /* i386_TARGET_ARCH || x86_64_TARGET_ARCH */
690
691
692
693 freeReg _               = 0#
694 globalRegMaybe _        = panic "X86.Regs.globalRegMaybe: not defined"
695
696 allArgRegs              = panic "X86.Regs.globalRegMaybe: not defined"
697 callClobberedRegs       = panic "X86.Regs.globalRegMaybe: not defined"
698
699
700 #endif
701
702