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