1 (* BEGIN INCLUDE FILE CONSTTYPE.incl.pascal *)
  2 
  3 (* HISTORY COMMENTS:
  4   1) change(86-09-11,JMAthane), approve(86-09-11,MCR7521),
  5      audit(86-09-15,JPFauche), install(86-11-12,MR12.0-1212):
  6      Release 8.03 for MR12
  7                                                    END HISTORY COMMENTS *)
  8 
  9 CONST                                           (*    VERSION 7.05 *)
 10                                                   (*  ARRAY'S   BOUNDS *)
 11 
 12   minno = 0 ;                                     (* MIN VALUE FOR NO  ;   SEE  TYPE NORANGE *)
 13   maxno = 63 ; (* MAX VALUE FORNO  ;    "     "    " *) { Modified for SimOne }
 14   ptlimit = 20 ;                                  (* MAX FOR   PTLIST     0 ..PTLIMIT *)
 15   displimit = 30 ;                                (*  "   "    DISPLAY       ..DISPLIMIT *)
 16   maxlabs = 50 ;                                  (*  "   "    LABTAB        ..MAXLABS *)
 17   fillimit = 50 ;                                 (*  "   "    FILPTS        .. FILLIMIT *)
 18   maxlevel = 20 ;                                 (*  SEE   LEVRANGE TYPE *)
 19   maxerrline = 16 ;                               (*  MAX  FOR   ERRINX *)
 20   maxerpg = 2 ;                                   (*  MAX  FOR  ERRORSFOUND, PAGESERRORS   0.. *)
 21   undmax = 1000 ;                                 (*  "    "   UNDLAB         1.. *)
 22   longalfbox = 16 ;                               (*  SEE  ALFAVALUE  TYPE *)
 23   lgparm = 100 ;                                  (*    PARMLIST  IN  $PARM *)
 24   lgparm1 = lgparm - 1 ;                          (*       LGPARM - 1 *)
 25   maxpredef = 99 ;                                (*   INITNAME         0 .. MAXPREDEF *)
 26   maxident = 32 ;                                 (*  LENGTH  MAX  FOR AN ID. *)
 27                                                   (* DONT MODIFY WITHOUT MODIFY maxident *)
 28                                                   (* IN optimized_procedures.alm *)
 29   maxnbofkeywords = 49 ;                          { Modified for SimOne }
 30 
 31   maxkeylength = 12 ; (* LENGTH MAX FOR A KEY-WORD *) { Modified for SimOne }
 32   maxexternname = 168 ;                           (* length max for an external name *)
 33   maxval = 256 ;                                  (*  LENGTH  MAX FOR  A STRING *)
 34   maxstring = 256 ;                               (*  MAX LENGTH FOR A STRING (STAND) <= MAXVAL *)
 35   alfaleng = 8 ;                                  (* SIZE  OF  ALFA TYPE *)
 36   maxfich = 50000 ;                               (*  FOR FICHINTER *)
 37   longboxlist = 20 ;                              (* MAX. NB. OF REG. BOXES *)
 38   maxref = 25 ;
 39   maxfield = 25 ;
 40 
 41 
 42   maxnewsize = 261094 ;                           (* MAX WORD SIZE FOR NEW *)
 43 
 44 (*  POWERS    OF  2 *)
 45   twoto4 = 2 * 2 * 2 * 2 ;
 46   twoto6 = twoto4 * 2 * 2 ;
 47   twoto8 = twoto6 * 2 * 2 ;
 48   twoto8m1 = twoto8 - 1 ;
 49   twoto9 = twoto8 * 2 ;
 50   twoto10 = twoto9 * 2 ;
 51   twoto12 = twoto10 * 2 * 2 ;
 52   twoto14 = twoto6 * twoto8 ;
 53   twoto15 = twoto14 * 2 ;
 54   twoto16 = twoto15 * 2 ;
 55   twoto17 = twoto16 * 2 ;
 56   twoto17m1 = twoto17 - 1 ;
 57   twoto18 = twoto17 * 2 ;
 58   twoto18m1 = twoto18 - 1 ;
 59   twoto27 = twoto18 * twoto9 ;
 60 
 61 (* COMPUTER'S  DESCRIPTION *)
 62 
 63   bitsinbyte = 9 ;
 64   bytesinword = 4 ;
 65   bytesinhword = bytesinword DIV 2 ;
 66   bytesindword = bytesinword * 2 ;
 67 
 68   wordsinpage = twoto10 ;
 69   pagesinsegment = twoto8 - 1 ;
 70   wordsinsegment = wordsinpage * pagesinsegment ;
 71   maxglobsize = twoto18 * bytesinword ;           (* MAX SIZE FOR GLOBALS IN BYTES *)
 72   maxstacksize = twoto15 * bytesinword ;          (* MAX SIZE FOR A STACK FRAME IN BYTES *)
 73   maxwseg = wordsinsegment ;                      (* MAX NBR OF WORDS IN SEGMENT = 255 * 1024 *)
 74 
 75   nilleft = '1FFFC0023'x ;                        (* VALUE FOR LEFT WORD OF THE "NIL" ITS *)
 76   nilright = '40000'x ;                           (* VALUE FOR RIGHT WORD OF THE "NIL" ITS *)
 77   packednil = '007777000001'o ;                   (* MULTICS PACKED NIL PTR *)
 78   bitsinword = bitsinbyte * bytesinword ;
 79   bitsinhword = bitsinbyte * bytesinhword ;
 80   bitsindword = 2 * bitsinword ;
 81   byteinbyte = 1 ;
 82   byteshift = 512 ;                               (* USED TO SHIFT AN INTEGER BY MULTIPLICATION *)
 83                                                   (* AND SUBSEQUENT VALUES *)
 84   maxint = 34359738367 ;                          (*  MAX. INTEGER *)
 85                                                   (* maxreal = 1.701411834604692317e38 ; *)
 86                                                   (* minreal = 1.469367938527859386e-39 ; *)
 87   racmaxint = 131072 ;                            (* USED TO AVOID OVERFLOW *)
 88                                                   (* IN INTEGER MULTIPLICATION *)
 89   ntwotobyte = twoto8 - 1 ;                       (* MAX. NUM. VALUE IN A BYTE *)
 90   ntwotohword = twoto17 - 1 ;                     (* MAX. NUM. VALUE IN A HALF. WORD *)
 91   stwotobyte = twoto9 - 1 ;                       (* MAX. SCAL. VALUE IN A BYTE *)
 92   setrange = 8 * bitsinword ;                     (*  SIZE OF STANDARD SETS : 8 WORDS MAX *)
 93   maxset = setrange - 1 ;                         (*  SETRANGE -1 *)
 94   maxerrnum = 3 * setrange - 1 ;                  (*   3*SETRANGE  -1 *)
 95   maxpage = maxerrnum ;
 96   maxchar = 127 ;                                 (*   < MAXSET *)
 97 
 98 (*     IN  LISTING *)
 99   maxpageline = 59 ;                              (*  MAX NUMBER OF LINES ON A LISTING'S PAGE *)
100   maxlinepascal = 400 ;
101   maxsliceline = 136 ;
102   lgprint = maxsliceline - 10 ;                   (*    SLICE  OF  PRINTED LINES *)
103 
104 (*  COMPILATION'S  RETURN  CODE *)
105 
106   errorcond = 8 ;
107   noerrorcond = 0 ;
108 
109   wordsforset = 8 ;
110   bytesforset = wordsforset * bytesinword ;       (* MAX. NUM. OF BYTES IN A SET *)
111   bitsforset = wordsforset * bitsinword ;         (* MAX. NUM. OF BITS  IN A SET *)
112   bornesupset = wordsforset - 1 ;
113   psrinbytes = 32 ;                               (* SIZE OF PSR REG. IN BYTES *)
114                                                   (* AND   EXTERNAL  CONSTRAINTS *)
115   maxdig = bitsinword DIV 3 ;                     (* MAX. NUMBER OF DIGITS IN OCTAL *)
116   maxexpon = 1000 ;                               (* TO AVOID OVERFLOW WITH EXPONENTS *)
117   maxhexdi = bitsinword DIV 4 ;                   (* MAX. NUMBER OF HEXA CHARS *)
118   max10 = 3435973835 ;                            (* TO AVOID OVERFLOW IN INTEGER CST *)
119   maxexp = 39 ;                                   (* MAX. SCALING FACTOR ALLOWED *)
120   minexp = -38 ;                                  (* MIN. SCALING FACTOR ALLOWED *)
121   maxdigitsinteger = 12 ;
122   maxdigitsreal = 20 ;
123   maxintegerstring = '+3435973836700000000' ;
124   maxrealstring = '+1701411834604692317' ;
125   minrealstring = '+1469367938527859386' ;
126 
127 (*  GENERATION   CONSTRAINTS  AND CONSTANTS *)
128   stackboundary = 16 * bytesinword ;              (*  BOUNDARY  FOR  A STACK  FRAME *)
129   maxrel = 132 ;                                  (*   LENGTH OF  PHYSICAL LINE *)
130   pascdebstacklocal = 384 ;                       (* BYTES DISP. OF FIRST FREE ST. IN PASCAL FRAME *)
131   simdebstacklocal = 448 ; (* BYTES DISP. OF FIRST FREE ST. IN  SIMONE FRAME *) { Modified for SimOne }
132   procparmsize = 24 ;                             (* SIZE FOR FORMAL PROCEDURE PARAMETERS *)
133   mathworksizew = 32 ;                            (* SIZE OF WORK AREA FOR MATH OPS *)
134   modulinitsize = 48 ;                            { Inserted for SimOne }
135   monitorinitsize = 88 ;                          { Inserted for SimOne }
136 
137 (* USEFUL   TOOLS *)
138   blank = '        ' ;
139   longblank = '                                ' ;
140 
141 (*   ALM   GENERATION CONSTANTS *)
142   bit29 = 64 ;                                    (* USE OF POINTER REGISTER BIT (BIT 29) *)
143   inhibit = 128 ;                                 (* INTERRUPT INHIBITION BIT (BIT28) *)
144   o41 = 33 ;                                      (*  ITS *)
145   o43 = 35 ;                                      (*  ITP *)
146 
147 
148 (* ENTRY POINTS OF OPERATORS *)
149 
150   log10switch = 6 ;
151                                                   (* Used in UNIQUE for predefinition of log10 *)
152                                                   (* and in EXPR for scientific subroutines    *)
153 
154   mainentryplace = 79 ;
155   extentryplace = 88 ;
156   checkbeforeeolnplace = 66 ;
157   checkbeforeeofplace = 67 ;
158   checkbeforetextreferenceplace = 68 ;
159   gotoexitextplace = 3 ;
160   intentryplace = 89 ;
161   scientplace = 80 ;
162   resetplace = 11 ;
163   rewriteplace = 12 ;
164   closeplace = 13 ;
165   readtextplace = 14 ;
166   readseqplace = 15 ;
167   readlnplace = 16 ;
168   writetextplace = 17 ;
169   writeseqplace = 18 ;
170   writelnplace = 19 ;
171   pageplace = 20 ;
172   puttextplace = 21 ;
173   putseqplace = 22 ;
174   gettextplace = 23 ;
175   getseqplace = 24 ;
176   gotoexitplace = 25 ;
177   newplace = 26 ;
178   disposeplace = 27 ;
179   resetheapplace = 28 ;
180   truncplace = 63 ;
181   roundplace = 64 ;
182   rafltplace = 31 ;
183   rqfltplace = 32 ;
184   putdirplace = 33 ;
185   getdirplace = 34 ;
186   fupdtplace = 35 ;
187   fcloseplace = 37 ;
188   connectplace = 36 ;
189   exceptcodeplace = 38 ;
190   intreturnplace = 39 ;
191   extreturnplace = 40 ;
192   returnzeroplace = 87 ;
193   intcallplace = 42 ;
194   extcallplace = 43 ;
195   initfsballocplace = 72 ;
196   dateopplace = 47 ;
197   timeopplace = 48 ;
198   clockopplace = 49 ;
199   longprofileplace = 50 ;
200   flushplace = 65 ;
201   fappendplace = 82 ;
202   freopenplace = 81 ;
203   argcshortplace = 69 ;
204   argcplace = 70 ;
205   argcextplace = 71 ;
206   argvshortplace = 73 ;
207   argvplace = 74 ;
208   argvextplace = 75 ;
209   stopshortplace = 76 ;
210   stopplace = 77 ;
211   stopextplace = 78 ;
212   sreadcharplace = 90 ;
213   sreadintegerplace = 91 ;
214   sreadrealplace = 92 ;
215   swritecharplace = 93 ;
216   swritestringplace = 94 ;
217   swritesubstringplace = 95 ;
218   swritebooleanplace = 96 ;
219   swriteintegerplace = 97 ;
220   swriterealeplace = 98 ;
221   swriterealdplace = 99 ;
222   swriteenumplace = 100 ;
223   parmproccheckplace = 101 ;
224   functionvaluesetplace = 102 ;
225   functionvaluecheckplace = 103 ;
226   extend_stack_op_place = 104 ;
227   reset_stack_end_op_place = 105 ;
228 
229 (* CONST USED WITH OPERATORS *)
230   transoptvptr = 40 ;                             (* DISP / PR7 OF TRANSFER VECTOR *)
231   lotptrdep = 22 ;                                (* DISP / PR7  LOT-PTR *)
232   pascoperatorsdep = 8 ;                          (* PASCAL OPERATORS *)
233                                                   (* EXECUTION BITS FOR STACK FRAME *)
234   mainbit = 131072 ;                              (* bit 18 *)
235   fastbit = 65536 ;                               (* bit 19 *)
236   checkbit = 32768 ;                              (* bit 20 *)
237   interactivebit = 16384 ;                        (* bit 21 *)
238   iowarningsbit = 8192 ;                          (* bit 22 *)
239   solstandardbit = 32 ;                           (* bit 30 *)
240   french_bit = 4 ;                                (* bit 31 *)
241 
242 (* PASCAL ERRORS CODES *)
243 
244   inxerrcode = 1 ;                                (* INDEX *)
245   chrerrcode = 2 ;                                (* FCT CHR *)
246   prderrcode = 3 ;                                (* FCT PRED *)
247   sucerrcode = 4 ;                                (* FCT SUCC *)
248   forerricode = 5 ;                               (* FOR INF *)
249   forerrscode = 6 ;                               (* FOR SUP *)
250   asserrcode = 7 ;                                (* ASSIGN *)
251   diverrcode = 8 ;                                (* DIV BY 0 *)
252   parerrcode = 9 ;                                (* PARAM. *)
253   caserrcode = 10 ;                               (* CASE *)
254   pckerrcode = 11 ;                               (* PACK/UNPK *)
255   seterrcode = 12 ;                               (* SET EXP *)
256   mlterrcode = 13 ;                               (* INTEGER MULT OVERFLOW *)
257   eofeolnerrcode = 14 ;                           (* Is eof or eoln meaningsfull *)
258   randinterrcode = 15 ;                           (* BAD BOUNDS FOR RANDINT *)
259   stringlength_range_error = 16 ;
260   stringlength_assignment_error = 17 ;
261   substring_offset_error = 18 ;
262   substring_negative_length_error = 19 ;
263   substring_too_long_error = 20 ;
264   delete_offset_error = 21 ;
265   delete_negative_length_error = 22 ;
266   delete_too_long_error = 23 ;
267   insert_overflow_error = 24 ;
268   bad_string_index = 25 ;
269   bad_date_time_parameter = 26 ;
270 
271 (* ** FOR CONFORMANT ARRAY *)
272 
273   confdimw = 4 ;                                  (*  FOUR ITS IN PARAMETERS LIST *)
274   dopevectorsize = 12 ;
275                                                   (* LO HI SIZE SUBSIZE *)
276   confdimsize = confdimw * bytesinword ;          (*  SAME IN BYTES *)
277 
278 (* STACK FRAME  DISPL. *)
279 
280   argptw = 26 ;                                   (* SAVE ARG POINTER ENTRY *)
281   next_sp_place = 18 ;                            (* MULTIC STACK_FRAME NEXT_SP *)
282   pr4depw = 36 ;                                  (* SAVE PR4 HERE *)
283   psrdepw = 56 ;                                  (* PSEUDO REGISTER FOR SET *)
284   psrdepb = 224 ;
285   dlkdepw = 32 ;                                  (* DYNAMIC LINK *)
286   fctdeplw = 34 ;                                 (* RETURNED VALUE FOR A FUNCTION *)
287   fctdepl = 136 ;
288   evareaw = 38 ;                                  (* WORKING EVEN STORAGE *)
289   fsbadrw = 68 ;                                  (* FSB STORED HERE FOR I/0 OPERATORS *)
290   valplacew = 70 ;                                (* VALUE TO BE WRITTEN OR POINTER ON IT *)
291   longplacew = 73 ;                               (* REQUESTED LENGTH *)
292   scaleplacew = 74 ;                              (* FOR REAL SCALING FACTOR *)
293   longstplacew = 74 ;                             (* REAL LENGTH FOR STRINGS *)
294 
295 (* INIT ZONE FOR LINKAGE SECTION *)
296 (* 8 WORDS HEADER *)
297 
298   firstglobal = 8 ;                               (* WORD OFFSET OF FIRST GLOBAL (EVEN) *)
299 
300 (* FSB DISPLACEMENTS *)
301 
302   lgfilename = 32 ;
303   iotextbuffersize = 400 ;
304   fdescsize = 152 ;
305   fsbpointersize = 8 ;
306   fstatusw = 7 ;
307   fposw = 21 ;
308   fsizew = 22 ;
309   fllengthw = 23 ;
310   fstatusb = 28 ;
311   fposb = 84 ;
312   fsizeb = 88 ;
313   fllengthb = 92 ;
314   eofw = 4 ;                                      (* WORD BOOLEAN EOF *)
315   eofb = 16 ;
316   eolnw = 27 ;                                    (* WORD BOOLEAN EOLN *)
317   eolnb = 108 ;
318 
319 (* PROFILE *)
320 
321   pclength = 2 ;                                  (* PROFILE COUNTER LENGTH IN WORDS *)
322   lpclength = 4 ;                                 (* LONG PROFILE COUNTER LENGTH IN WORDS *)
323   phl = 0 ;                                       (* PROFILE HEADER LENGTH *)
324   lphl = 13 ;                                     (* LONG PROFILE HEADER LENGTH IN WORDS *)
325 
326 (* RELOCATION CODES *)
327 
328   link18 = '900000000'x ;                         (* "10010"b *)
329   link15 = 'A00000000'x ;                         (* "10100"b *)
330   int18 = 'C00000000'x ;                          (* "11000"b *)
331   self_rel = '880000000'x ;                       (* "10001"b *)
332   int15 = 'C80000000'x ;                          (* "11001"b *)
333   prof = 'D00000000'x ;                           (* "11010"b *)
334   absl = '000000000'x ;                           (* "0"b *)
335   symb = 'B00000000'x ;                           (* "10110"b *)
336 
337   (*  CONSTANTES USED BY SIMONE COMPILER *)       { Inserted for SimOne }
338   maxchar8 = 255 ;
339   mofatherdisp = 1 ; (* DIFFERENCE BETWEEN ADDR OF FATHER WHOSE TYPE IS MONORMOD *) { Inserted for SimOne }
340   procfatherdisp = 0 ; (* OR WHOSE TYPE IS PROC *) { Inserted for SimOne }
341   procmodlkw = 104 ;                              { Inserted for SimOne }
342   modynlk = 0 ;                                   { Inserted for SimOne }
343   condcounterplace = 16 ; (* BYTES DIP. OF CONDITION COUNTER *) { Inserted for SimOne }
344   moarglistw = 6 ; (* DEPLACEMENT OF ARGLIST IN MONITOR OR MODULE PSEUDO_STACK *) { Inserted for SimOne }
345   baseprocessdplmt = 100 ;                        { Inserted for SimOne }
346   executionmodplmt = 106 ;                        { Inserted for SimOne }
347   maindplmt = 0 ;
348   processlocaldplmt = 96 ;
349   (* ENTRY POINTS OF OPERATORS *)                 { Inserted for SimOne }
350                                                   { Inserted for SimOne }
351   simainentryplace = -1 ;                         { Inserted for SimOne }
352   simintentryplace = -2 ;                         { Inserted for SimOne }
353   simintreturnplace = -3 ;                        { Inserted for SimOne }
354   processentryplace = -4 ;                        { Inserted for SimOne }
355   settinginactivequeueplace = -5 ;                { Inserted for SimOne }
356   waitsonsplace = -6 ;                            { Inserted for SimOne }
357   processreturnplace = -7 ;                       { Inserted for SimOne }
358   holdplace = -8 ;                                { Inserted for SimOne }
359   savearglistplace = -9 ;                         { Inserted for SimOne }
360   modulentryplace = -10 ;                         { Inserted for SimOne }
361   monitorentryplace = -11 ;                       { Inserted for SimOne }
362   initcondplace = -12 ;                           { Inserted for SimOne }
363   askforexclusionplace = -13 ;                    { Inserted for SimOne }
364   freeexclusionplace = -14 ;                      { Inserted for SimOne }
365   signalplace = -15 ;                             { Inserted for SimOne }
366   waitplace = -16 ;                               { Inserted for SimOne }
367   emptyplace = -17 ;                              { Inserted for SimOne }
368   lengthplace = -18 ;                             { Inserted for SimOne }
369   priorityplace = -19 ;                           { Inserted for SimOne }
370   vtimeplace = -20 ;                              { Inserted for SimOne }
371   terminateplace = -21 ;                          { Inserted for SimOne }
372   mowaitsonsplace = -22 ;                         { Inserted for SimOne }
373   uniformplace = -23 ;                            { Inserted for SimOne }
374   normalplace = -24 ;                             { Inserted for SimOne }
375   negexpplace = -25 ;                             { Inserted for SimOne }
376   randintplace = -26 ;                            { Inserted for SimOne }
377   pureentryplace = -27 ;
378   simextentryplace = -28 ;
379   exitplace = -29 ;
380   restorprevmoplace = -30 ;
381                                                   { Inserted for SimOne }
382   lcprocess = 96 ; (* BYTES SIZE OF THE LOCAL VARIABLES IN THE STACK OF A PROCESS *) { Inserted for SimOne }
383                                                   { Inserted for SimOne }
384                                                   { Inserted for SimOne }
385   emptyindex = 4 ;                                { Inserted for SimOne }
386                                                   { Inserted for SimOne }
387                                                   (* DEFAULT  LENGTH  FOR EDITION *)
388   deflreal = 24 ;
389   deflnum = 12 ;
390   deflbool = 4 ;
391   deflchar = 1 ;
392 
393 
394 
395 (*$PAGE *)
396 TYPE
397   numberstring = PACKED ARRAY [1..maxdigitsreal] OF char ;
398   alfa = PACKED ARRAY [1..alfaleng] OF char ;
399   alfaid = PACKED ARRAY [1..maxident] OF char ;
400   externid = PACKED ARRAY [1..maxexternname] OF char ;
401   alfalistptr = ^alfalist ;
402   alfalist = RECORD
403     previous, next : alfalistptr ;
404     name : alfaid
405   END ;
406   idkinds = (actual, formal, arraybound, exportable, imported) ;
407 
408 (*  ACTUAL  MEANS STANDARD  PASCAL  PROC/VARS
409    FORMAL  USED  FOR VAR  PARAMETERS
410    EXPORTABLE     'DEF'  PROC/VARS
411    IMPORTED     APPEARS  IN EXTERNAL  LIST.  MUST BE REDEFINED *)
412   typform = (reel, numeric, scalar, pointer, power, arrays, records, monormod, { Modified for SimOne }
413     condition, files, aliastype) ;                { Modified for SimOne }
414                                                   { Modified for SimOne }
415   idklass = (schema, types, konst, proc, vars, field, tagfield, dummyclass) ;
416   consttype = (wordconst, dwordconst, alfaconst) ;
417   idprocdef = (standdef, forwdef, extdef, initdef, finitdef) ; { Modified for SimOne }
418   levrange = 0..maxlevel ;
419   alfapt = @alfavalue ;
420   alfavalue = RECORD
421     nextval : alfapt ;                            (* NEXT VALUE BOX FOR  SAME STRING *)
422     alfaval : PACKED ARRAY [1..longalfbox] OF char ;
423     longfill : integer ;                          (* USED PART OF  ALFAVAL IN  THIS BOX *)
424   END ;
425   refptr = @reflist ;
426   reflist = RECORD
427     nextref : refptr ;
428     refnbr : integer ;
429     refs : ARRAY [1..maxref] OF RECORD
430       filen, linen, sttmapind, place : integer ;
431     END ;
432   END ;
433   ctp = @contexttable ;
434   setofno = SET OF minno..maxno ;
435   stdkind = (stdpure, stdcompiler, stdsol, stdextend, stdcomputer) ;
436   typusednames = ARRAY [1..6] OF alfaid ;
437   filelocation = (notafile, permanentfile, workfile, localfile, standardfile) ;
438 
439   proclocation = (notpredef, instdpure, instdcompiler, instdsol,
440     instdextend, instdcomputer, instdsimone) ;    { Modified for SimOne }
441   externalitemtype = (extnotresolved, externalarea, exportvar, importvar,
442     exportproc, importproc, localproc, mainprogram, remanentfile,
443     requiredfile, runtimeentry) ;
444   ptexternalitem = ^ externalitem ;
445   externalitem = RECORD
446     extname : alfaid ;
447     extsegname, extgenerator, extentryname : alfaid ;
448     extnext : ptexternalitem ;
449     extrfile1, extrline1, extrfile2, extrline2 : integer ;
450     extdecl : ctp ;
451     extitemtype : externalitemtype ;
452     extkind : idkinds ;
453     extpltdisp : integer ;
454     extareadisp : integer ;
455     extlong : integer ;
456     extwantdescs : boolean ;
457   END ;
458   (* TYPES USED BY SIMONE COMPILER *)             { Inserted for SimOne }
459   motypes = (module, monitor) ;                   { Inserted for SimOne }
460   objaccessibles = (modul, monit, condit) ;       { Inserted for SimOne }
461   ensaccessible = SET OF objaccessibles ;         { Inserted for SimOne }
462   incbloc = (monitormodule, subroutine) ;         { Inserted for SimOne }
463                                                   { Inserted for SimOne }
464   nodeptr = @node ;                               { Inserted for SimOne }
465                                                   { Inserted for SimOne }
466   node = RECORD { USED FOR SPACE COMPUTATION }    { Inserted for SimOne }
467     inthelist, compiled, recursive : boolean ;    { Inserted for SimOne }
468     sizemax : integer ;                           { Inserted for SimOne }
469     proce : ctp ;                                 { Inserted for SimOne }
470   END ;                                           { Inserted for SimOne }
471   nodelistptr = @nodelistelem ;                   { Inserted for SimOne }
472                                                   { Inserted for SimOne }
473   nodelistelem = RECORD                           { Inserted for SimOne }
474     previousnode, nextnode : nodelistptr ;        { Inserted for SimOne }
475     elem : nodeptr ;                              { Inserted for SimOne }
476   END ;                                           { Inserted for SimOne }
477                                                   { Inserted for SimOne }
478   exitptr = @exitelem ;                           { Inserted for SimOne }
479   exitelem = RECORD (* ONE FOR EACH EXIT STATEMENT *) { Inserted for SimOne }
480     nextexitelem : exitptr ;                      { Inserted for SimOne }
481     exitdplmt : integer ;                         { Inserted for SimOne }
482   END ;                                           { Inserted for SimOne }
483 
484   ftp = ^schema_token ;
485   schema_status = RECORD
486     on : boolean ;
487     schema_ptr : ctp ;
488     current_token : ftp ;
489     current_parameter : ctp ;
490   END ;
491   schema_token_kind = (symbol_token, name_token, int_const_token, char_const_token, real_const_token) ;
492   schema_token = RECORD
493     next : ftp ;
494     CASE kind : schema_token_kind OF
495     symbol_token : (tno, tcl : integer) ;
496     name_token : (taval : alfaid) ;
497     int_const_token : (t_int_value : integer) ;
498     real_const_token : (t_real_value : real) ;
499     char_const_token : (t_char_value : char) ;
500   END ;
501 
502 (* DONT MODIFY CONTEXTABLE DECLARATION
503    WITHOUT CHECKING :
504    nameplaceincontextable
505    AND nxtelplaceincontextable
506    IN optimized_procedures.alm *)
507   contexttable = RECORD
508     name : alfaid ;
509     nxtel : ctp ;
510     alfathread : ctp ;
511     deffile, defline : integer ;
512     references : refptr ;
513     symbolplace : integer ;                       (* PCK PTR TO SYMBOL NODE IN SYMB TB *)
514     symbtablerefs : integer ;                     (* BACKWARD THREAD OF REFS IN TEXT TO SYMBOL TABLE *)
515     CASE klass : idklass OF
516     schema : (
517       top_for_schema : integer ;                  (* CONTEXT AT SHEMA DECLARATION TIME *)
518       next_for_schema : ctp ;
519       formal_parameter_list : ctp ;
520       parameter_count : integer ;
521       token_list : ftp ;
522       type_description : ctp) ;
523     types : (
524       size, cadrage : integer ;
525       pack : boolean ;
526       tlevel : levrange ;
527       objaccedes : ensaccessible ; { TO ALLOW VARIABLES ' DECLARATIONS } { Inserted for SimOne }
528                                                   (* *** BEGIN SCHEMA INFO *** *)
529       father_schema : ctp ;
530       actual_parameter_list : ctp ;
531       desc_vector_references : integer ;
532                                                   (* *** END SCHEMA INFO *** *)
533       CASE form : typform OF
534       reel : () ;
535       numeric : (npksize, nmin, nmax : integer) ;
536       scalar : (spksize : integer ;
537         CASE subrng : boolean OF
538         false : (fconst, sptcstepw : ctp) ;
539         true : (smin, smax : integer ;
540           typset : ctp) ;) ;
541       pointer : (ptpksize : integer ;
542         domain, eltype : ctp) ;
543       power : (ppksize : integer ;
544         elset : ctp ;
545         setlength : integer) ;
546       arrays : (aeltype, inxtype : ctp ;
547 
548         CASE conformant : boolean OF
549         false : (lo, hi, opt2, subsize : integer) ;
550         true : (
551           pthigh, ptlow : ctp ;
552           ) ;
553         ) ;
554       records : (recvar, fstfld : ctp) ;
555       files : (feltype : ctp ;
556         ) ;
557       monormod : (motype : motypes ;              { Inserted for SimOne }
558         niveau : levrange ;                       { Inserted for SimOne }
559         moaddr, nbparmo : integer ;               { Inserted for SimOne }
560         ptpar, ptvarloc, ptentr : ctp ;           { Inserted for SimOne }
561         initmoproc, finitmoproc, blocenglob : ctp) ; { Inserted for SimOne }
562       condition : () ;                            { Inserted for SimOne }
563       aliastype : (realtype : ctp) ;) ;
564     konst : (
565       succ, contype : ctp ;
566       CASE typofconst : consttype OF
567       wordconst : (values : integer) ;
568       dwordconst : (valreel : real) ;
569       alfaconst : (alfadeb : alfapt ;
570         alfalong, alfalevel, unddeb : integer) ;) ;
571     proc : (proctype, formals : ctp ;
572       prockind : idkinds ;
573       proclevel : levrange ;
574       procaddr, segsize, nbparproc, locincode : integer ;
575       procisassigned, predefproc, procinscope, pisrefincode : boolean ;
576       phasdescriptor : boolean ;                  (* TRUE IF HAS CONF ARRAY PARAMETERS *)
577       ploc : proclocation ;
578       procextitem : ptexternalitem ;
579       ptypesymbolplace : integer ;                (* PACKED PTR TO TYPE BOX IN SYMBOL TB *)
580       recur : integer ;                           { Inserted for SimOne }
581       procaccesslevel : levrange ;                { Inserted for SimOne }
582       processus, pure : boolean ;                 { Inserted for SimOne }
583       chaineentree : ctp ;                        { Inserted for SimOne }
584       procnode : nodeptr ;                        { Inserted for SimOne }
585       procincbloc : incbloc ; (* BLOC CONTAINING THIS PROC *) { Inserted for SimOne }
586       procfirstexit : exitptr ; (* TO CHAIN EXIT STATEMENT *) { Inserted for SimOne }
587       procfirsttofinit : ctp ; (* FIRST VAR TO BE FINALIZED IN THIS PROCESS, ALWAYS NIL FOR A PROCEDURE *) { Inserted for SimOne }
588       procstackinitsize : integer ;               { Inserted for SimOne }
589       procwasforwarddef : boolean ;               { Inserted for SimOne }
590       procdef : idprocdef ;
591       pwantdescs : boolean ;                      (* TRUE IF PROC WAS DECLARED EXT DESCRIPTORS *)
592       pdescsaddrplace : integer ;                 (* PLACE IN STATICS OF PTR TO DESCRS VECTOR - IF PREV. TRUE *)
593       procisactive : boolean ;                    (* TRUE IF COMPILER IS ANALYZING BODY OF THIS PROC *)
594       pextcalltrapinfoplace : integer ;           (* WORD OFFSET OF TRAP INFO FOR EXT CALL - ONLY IF DESCS *)
595       pwantspl1descriptors : boolean) ;           (* TRUE IF PL1 DESCRIPTORS NEEDED *)
596     vars : (vtype : ctp ;
597       vkind : idkinds ;
598       vfilelocation : filelocation ;
599       vaddr : integer ;
600       vdispl, vdescaddr : integer ;
601       vlevel : levrange ;
602       vlink_is_generated : boolean ;
603       visused, visset, visreadonly, varparam, visrefincode : boolean ;
604       vnexttofinit : ctp ; (* TO CHAIN VAR TO BE FINIT *) { Inserted for SimOne }
605       varmo : boolean ; (* TRUE IF VAR IS DECLARE IN A MONITOR OR A MODULE *) { Inserted for SimOne }
606       vfather : ctp ; (* PTR ON THE MONITOR OR THE MODULE CONTAINING VAR *) { Inserted for SimOne }
607       vptextitem : ptexternalitem) ;
608     field : (fldtype : ctp ;
609       fldaddr, bytwidth : integer) ;
610     tagfield : (casesize : integer ;
611       variants : ctp ;
612       CASE tagval : boolean OF
613       false : (casetype : ctp ; selectorfield : ctp) ;
614       true : (caseval : integer ; firstfield : ctp) ;) ;
615     dummyclass : () ;
616   END ;                                           (* RECORD CONTEXTTABLE *)
617                                                   (* NOW  OTHER TYPES *)
618 
619   shrtint = -twoto17..twoto17m1 ;
620   bytint = -twoto8..twoto8m1 ;
621   norange = minno..maxno ;
622   where = (block, cwith, vwith) ;                 (* USED TO DESCRIBE AN IDENTIFIER *)
623   contexte = (data, code, linkage, definition, deccode) ; { Modified for SimOne }
624   levtrace = (none, low, medium, high) ;
625                                                   (* DONT MODIFY RECIDSCOPE DECLARATION *)
626   withreflist = RECORD
627     nbr : 0..maxfield ;
628     symbolp : ARRAY [1..maxfield] OF ctp
629   END ;
630                                                   (* WITHOUT CHECK : *)
631                                                   (* recidscopelength IN optimized_procedures.alm *)
632   recidscope = RECORD                             (* ELEMENT OF  DISPLAY *)
633     fname : ctp ;
634     CASE occur : where OF
635     block : () ;
636     cwith : (creflist : withreflist ; clevel : levrange ; cdspl : integer) ;
637     vwith : (vreflist : withreflist ; vdspl : integer ; vpack : boolean) ;
638   END (* REC-ID-SCOPE *) ;
639   blocknodeptr = @blocknode ;
640   labelblockptr = ^labelblock ;                   (* BOXES FOR LABELS *)
641   labelblock = RECORD
642     number : integer ;                            (* LABEL ID *)
643     locinbytes : integer ;                        (* LOCATION IN TEXT SECTION (BYTES) *)
644     next : labelblockptr ;                        (* NEXT IN LABELS LIST *)
645     brother : labelblockptr ;                     (* THREAD FOR LABELS OF SAME BLOCK *)
646     procnode : blocknodeptr ;                     (* PTR TO PROCEDURE NODE *)
647     dclfile, dclline : integer ;                  (* FILE, LINE FOR DECLARATION *)
648     deffile, defline : integer ;                  (* FILE, LINE OF LOCATION *)
649     references : refptr ;                         (* PTR TO REFERENCES BOX(ES) *)
650     ref_allowed : RECORD
651       ic_from, ic_to : integer
652     END ;
653     next_in_block : labelblockptr ;
654   END ;
655   label_pdl_element = RECORD
656     previous, next : ^label_pdl_element ;
657     first : labelblockptr ;
658   END ;
659   labdescr = RECORD                               (* ELEMENT  OF  LABTAB *)
660     labval, lablev, labexit, labch1, labdef : integer ;
661     labbox : labelblockptr ;
662   END (* REC *) ;
663   lab_pdl_ptr = ^lab_pdl_element ;
664   lab_pdl_element = RECORD
665     previous, next : lab_pdl_ptr ;
666     first_in_block : labelblockptr ;
667     start : integer
668   END ;
669   typofsymb = (irrelsy, begsy, endsy) ;
670   occurence = RECORD                              (* ELEMENT OF UNDLAB *)
671     succ, place : shrtint ;
672   END (* REC *) ;
673                                                   (* TYPES  USED IN CODE GENERATION *)
674 
675 (*  ALM INSTRUCTIONS , I+MNEMONIC. INSTRUCTIONS ARE GROUPED BY FUNCTIONS. IN
676    EACH FUNCTION, THE ORDER IS THE ONE OF THE AL39 MANUAL EXCEPT FOR EIS
677    MULTIWORD. IN THIS LAST GROUP, THE ORDER MAKES EASIER THE CODE GENERATION *)
678 (* FIXED-POINT STANDARD INSTRUCTIONS ****** *)
679   instword = (ieaa, ieaq, ieax0, ieax1, ieax2, ieax3, ieax4, ieax5,
680     ieax6, ieax7, ilca, ilcaq, ilcq, ilcx0, ilcx1, ilcx2,
681     ilcx3, ilcx4, ilcx5, ilcx6, ilcx7, ilda, ildac, ildaq,
682     ildi, ildq, ildqc, ildx0, ildx1, ildx2, ildx3, ildx4,
683     ildx5, ildx6, ildx7, ilreg, ilxl0, ilxl1, ilxl2, ilxl3,
684     ilxl4, ilxl5, ilxl6, ilxl7, isreg, ista, istac, istacq,
685     istaq, istc1, istc2, istcd, isti, istq, istt, istx0,
686     istx1, istx2, istx3, istx4, istx5, istx6, istx7, istz,
687     isxl0, isxl1, isxl2, isxl3, isxl4, isxl5, isxl6, isxl7,
688     ialr, ials, iarl, iars, illr, ills, ilrl, ilrs,
689     iqlr, iqls, iqrl, iqrs, iada, iadaq, iadl, iadla,
690     iadlaq, iadlq, iadlx0, iadlx1, iadlx2, iadlx3, iadlx4, iadlx5,
691     iadlx6, iadlx7, iadq, iadx0, iadx1, iadx2, iadx3, iadx4,
692     iadx5, iadx6, iadx7, iaos, iasa, iasq, iasx0, iasx1,
693     iasx2, iasx3, iasx4, iasx5, iasx6, iasx7, iawca, iawcq,
694     isba, isbaq, isbla, isblaq, isblq, isblx0, isblx1, isblx2,
695     isblx3, isblx4, isblx5, isblx6, isblx7, isbq, isbx0, isbx1,
696     isbx2, isbx3, isbx4, isbx5, isbx6, isbx7, issa, issq,
697     issx0, issx1, issx2, issx3, issx4, issx5, issx6, issx7,
698     iswca, iswcq, impf, impy, idiv, idvf, ineg, inegl,
699     icmg, icmk, icmpa, icmpaq, icmpq, icmpx0, icmpx1, icmpx2,
700     icmpx3, icmpx4, icmpx5, icmpx6, icmpx7, icwl, iszn, isznc,
701                                                   (* FLOATING-POINT INSTRUCTIONS ************* *)
702     idfld, ifld, idfst, idfstr, ifst, ifstr, idfad, idufa,
703     ifad, iufa, idfsb, idufs, ifsb, iufs, idfmp, idufm,
704     ifmp, iufm, idfdi, idfdv, ifdi, ifdv, ifneg, ifno,
705     idfrd, ifrd, idfcmg, idfcmp, ifcmg, ifcmp, iade, ifszn,
706     ilde, iste,
707                                                   (* BOOLEAN INSTRUCTIONS ******************** *)
708     iana, ianaq, ianq, iansa, iansq, iansx0, iansx1, iansx2,
709     iansx3, iansx4, iansx5, iansx6, iansx7, ianx0, ianx1, ianx2,
710     ianx3, ianx4, ianx5, ianx6, ianx7, iora, ioraq, iorq,
711     iorsa, iorsq, iorsx0, iorsx1, iorsx2, iorsx3, iorsx4, iorsx5,
712     iorsx6, iorsx7, iorx0, iorx1, iorx2, iorx3, iorx4, iorx5,
713     iorx6, iorx7, iera, ieraq, ierq, iersa, iersq, iersx0,
714     iersx1, iersx2, iersx3, iersx4, iersx5, iersx6, iersx7, ierx0,
715     ierx1, ierx2, ierx3, ierx4, ierx5, ierx6, ierx7, icana,
716     icanaq, icanq, icanx0, icanx1, icanx2, icanx3, icanx4, icanx5,
717     icanx6, icanx7, icnaa, icnaaq, icnaq, icnax0, icnax1, icnax2,
718     icnax3, icnax4, icnax5, icnax6, icnax7,
719                                                   (* POINTER REGISTERS INSTRUCTIONS ********** *)
720     ieasp0, ieasp1, ieasp2, ieasp3, ieasp4, ieasp5, ieasp6, ieasp7,
721     ieawp0, ieawp1, ieawp2, ieawp3, ieawp4, ieawp5, ieawp6, ieawp7,
722     iepbp0, iepbp1, iepbp2, iepbp3, iepbp4, iepbp5, iepbp6, iepbp7,
723     iepp0, iepp1, iepp2, iepp3, iepp4, iepp5, iepp6, iepp7,
724     ilpri, ilprp0, ilprp1, ilprp2, ilprp3, ilprp4, ilprp5, ilprp6,
725     ilprp7, ispbp0, ispbp1, ispbp2, ispbp3, ispbp4, ispbp5, ispbp6,
726     ispbp7, ispri, ispri0, ispri1, ispri2, ispri3, ispri4, ispri5,
727     ispri6, ispri7, isprp0, isprp1, isprp2, isprp3, isprp4, isprp5,
728     isprp6, isprp7, iadwp0, iadwp1, iadwp2, iadwp3, iadwp4, iadwp5,
729     iadwp6, iadwp7, iepaq,
730                                                   (* TRANSFER INSTRUCTIONS ******************* *)
731     icall6, iret, irtcd, iteo, iteu, itmi, itmoz, itnc,
732     itnz, itov, itpl, itpnz, itra, itrc, itrtf, itrtn,
733     itsp0, itsp1, itsp2, itsp3, itsp4, itsp5, itsp6, itsp7,
734     itss, itsx0, itsx1, itsx2, itsx3, itsx4, itsx5, itsx6,
735     itsx7, ittf, ittn, itze,
736                                                   (* MISCELLANEOUS INSTRUCTIONS ************** *)
737     irccl, idrl, ixec, ixed, imme, imme2, imme3, imme4,
738     inop, ipuls1, ipuls2, isra, isbar, ibcd, igtb,
739                                                   (* PRIVILEGED INSTRUCTIONS ***************** *)
740     ilbar, ilcpr, ildbr, ildt, ilptp, ilptr, ilra, ilsdp,
741     ilsdr, ircu, iscpr, iscu, isdbr, isptp, isptr, issdp,
742     issdr, icamp, icams, irmcm, irscr, irsw, icioc, ismcm,
743     ismic, isscr, iabsa, idis,
744                                                   (* SINGLE WORD EIS INSTRUCTIONS ************ *)
745     iaar0, iaar1, iaar2, iaar3, iaar4, iaar5, iaar6, iaar7,
746     ilar0, ilar1, ilar2, ilar3, ilar4, ilar5, ilar6, ilar7,
747     ilareg, ilpl, inar0, inar1, inar2, inar3, inar4, inar5,
748     inar6, inar7, iara0, iara1, iara2, iara3, iara4, iara5,
749     iara6, iara7, iarn0, iarn1, iarn2, iarn3, iarn4, iarn5,
750     iarn6, iarn7, isar0, isar1, isar2, isar3, isar4, isar5,
751     isar6, isar7, isareg, ispl, ia4bd, ia6bd, ia9bd, iabd,
752     iawd, is4bd, is6bd, is9bd, isbd, iswd,
753                                                   (* MULTI-WORDS EIS INSTRUCTIONS ************ *)
754     itct, itctr, icmpc, iscm, iscmr, imlr, imrl, imvt,
755     icsl, icsr, isztl, isztr, iscd, iscdr, icmpn, imvn,
756     icmpb, ibtd, idtb, iad2d, isb2d, imp2d, idv2d, imve,
757     imvne, iad3d, isb3d, imp3d, idv3d,
758                                                   (* REPEAT INSTRUCTIONS ********************* *)
759     irpd, irpl, irpt,
760                                                   (* STBA, STBQ ,STCA AND STCB INSTRUCTIONS ** *)
761     istba, istbq, istca, istcq) ;
762                                                   (* ADDRESS MODIFICATIONS  , *)
763                                                   (* T+MNEMONIC  AND Y USED FOR *  , *)
764                                                   (* TZ = ILLEGAL MODIFIER *)
765                                                   (* BINARY CODE IS OBTAINED WITH THE ORD FUNCTION *)
766   tag = (tn, tau, tqu, tdu, tic, tal, tql, tdl,   (* R  MOD *)
767     tx0, tx1, tx2, tx3, tx4, tx5, tx6, tx7,
768     tny, tauy, tquy, tz23, ticy, taly, tqly, tz27, (* RI MOD *)
769     tx0y, tx1y, tx2y, tx3y, tx4y, tx5y, tx6y, tx7y,
770     tf1, titp, tz42, tits, tsd, tscr, tf2, tf3,   (* IT MOD *)
771     tci, ti, tsc, tad, tdi, tdic, tid, tidc,
772     tz60, tyau, tyqu, tydu, tyic, tyal, tyql, tydl, (* IR MOD *)
773     tyx0, tyx1, tyx2, tyx3, tyx4, tyx5, tyx6, tyx7) ;
774   register = (nreg, pr1, pr2, pr5, pr7, pr3, pr0, prstatic, prlink, pr6,
775     nxreg, x0, x1, x2, x3, x4, x5, x6, x7,
776     xbidon, ra, rq, raq, reaq, psr, re, ri) ;     (* USED REGISTERS *)
777   preg = nreg..pr6 ;                              (* POINTER REGISTERS - SUBRANGE OF REGISTER *)
778   mreg = tn..tx7 ;                                (* ADDRESS MODIFICATIONS WITHOUT INDIRECTION *)
779                                                   (* - SUBRANGE OF TAG *)
780                                                   (* SUBRANGES OF INSTWORD USED IN CODE GENERATION *)
781   istand = ieaa..iswd ;                           (* STANDARD INSTRUCTIONS *)
782   ieism = icmpc..idv3d ;                          (* EIS MULTIWORD INSTRUCTIONS *)
783   irept = irpd..irpt ;                            (* REPEAT INSTRUCTIONS *)
784   istobc = istba..istcq ;                         (* STORE BYTES OR CHARACTERS INSTRUCTIONS *)
785   lgcar = (l4, l6, l9) ;                          (* CHARACTER DATA TYPE - NUMBER = LENGTH IN BITS *)
786   typsig = (flls, fxls, fxts, fxns) ;             (* SIGN AND DECIMAL TYPES,FL=FLOATING-POINT, *)
787                                                   (* FX=FIXED-POINT,LS= LEADING SIGN *)
788                                                   (* TS= TRAILING SIGN *)
789                                                   (* NS= NO SIGN *)
790                                                   (* BIT VALUES FOR CODE GENERATION *)
791   zptr = (p0t0r0, p0t0r1, p0t1r0, p0t1r1, p1t0r0, p1t0r1, p1t1r0, p1t1r1) ; (* BITS 0,9 *)
792                                                   (* AND 10 OF EIS MULTIWORD INSTRUCTIONS *)
793                                                   (* P=SIGN OR FILL BIT , T=TRUNCATION BIT , *)
794                                                   (* R=ROUNDING FLAG BIT *)
795   zabc = (a0b0c0, a0b0c1, a1b0c0, a1b0c1, a0b1c0, a0b1c1, a1b1c0, a1b1c1) ; (* BITS 8,9 *)
796                                                   (* AND 10 OF REPEAT INSTRUCTIONS *)
797                                                   (* A AND B = USE OF DELTA FIELD , *)
798                                                   (* C = USE OF X0 REGISTER *)
799   zari = (a0r0i0, a0r0i1, a0r1i0, a0r1i1, a1r0i0, a1r0i1, a1r1i0, a1r1i1) ; (* BITS 0,1 *)
800                                                   (* AND 2  OF EIS MODIFICATION FIELDS *)
801                                                   (* A=USE OF ADDRESS REGISTER , *)
802                                                   (* R = OPERAND LENGTH FIELD GIVES A REGISTER *)
803                                                   (* I= USE OF INDIRECTION FOR *)
804                                                   (* THE OPERAND DESCRIPTOR *)
805 
806 (* USED ONLY IN CONDITIONNAL COMPILATION FOR COMPILER'S CONTROLS *)
807   forset = (s0, s1, s2, s3, s4, s5) ;             (* USED TO GIVE FORBIDDEN TAGS/PTR FOR ISTAND/ *)
808                                                   (* IEISM *)
809   halfword = integer ;                            (* USED FOR FICHINTER *)
810   binartype = PACKED ARRAY [1..maxfich] OF halfword ; (* FICHINTER *)
811   binartypeptr = ^binartype ;
812   attrkind = (varbl, lcond, lval, chain, sval) ;
813   attraccess = (direct, pointee, pointable, encode) ;
814   destination = (inacc, inq, inaq, inpsr, inpr, out) ;
815   setarray = ARRAY [0..bornesupset] OF integer ;
816   regpt = @regbox ;
817   regbox = RECORD                                 (* BOX DESCRIBING A LOADED REGISTER *)
818                                                   (* AND MEMORIZING SAVING INFORMATIONS *)
819     sregister : register ;                        (* LOADED REGISTER *)
820     saveplace : integer ;                         (* BYTES DISP. /PR6 OF SAVING STORAGE *)
821     nextbloc : regpt ;                            (* POINTS PREVIOUS BLOC.(NOT NEXT.) *)
822     predbloc : regpt ;                            (* POINTS NEXT BLOC. (NOT PRED.) *)
823   END ;                                           (* REGBOX *)
824   wcstpt = @iunresolv ;
825   rcstpt = @runresolv ;
826   lcstpt = @liunresolv ;
827   llcstpt = @lliunresolv ;
828   iunresolv = RECORD
829     valu : integer ;
830     cstplace : integer ;                          (* ENTRY IN UNDLAB *)
831     cstnext : wcstpt ;                            (* LINKAGE OF WORD CSTES *)
832   END ;
833   runresolv = RECORD
834     rvalu : real ;
835     rplace : integer ;                            (* ENTRY IN UNDLAB *)
836     rnext : rcstpt ;                              (* LINKAGE OF REAL CSTES *)
837   END ;
838   liunresolv = RECORD
839     lvalu : setarray ;
840     lplace : integer ;                            (* ENTRY IN UNDLAB *)
841     lnext : lcstpt ;                              (* LINKAGE OF LONG CSTES *)
842   END ;
843   lliunresolv = RECORD
844     llvalu : setarray ;                           (* SET CSTE *)
845     llplace : integer ;                           (* ENTRY ON UNDLAB *)
846     llnext : llcstpt ;                            (* LINKAGE OF SET CSTES *)
847   END ;
848 
849   attr = RECORD
850 
851     typtr : ctp ;                                 (* TYPE OF DESCRIBED ITEM *)
852     CASE kind : attrkind OF
853 
854     varbl : (                                     (*  ITEM IS ANYWHERE IN STORAGE *)
855       vlev : levrange ;                           (* DEFINITION LEVEL *)
856       basereg : preg ;                            (* BASIS TO ACCES ITEM, *)
857                                                   (* OR ITS TO ITEM IF POINTABLE *)
858       basebloc : regpt ;
859                                                   (* POINTS THE BOX DESCRIBING BASEREG; *)
860                                                   (* NIL FOR PR4,PR6 *)
861       dplmt : integer ;                           (* BYTES DISPLACEMENT TO ADD AT FINAL ADDRESS *)
862       inxreg : register ;                         (* MODIFICATION REGISTER CONTAINING WORDS DISP *)
863                                                   (* RA  ==>  A 18..35  USED *)
864                                                   (* RQ  ==>  Q 18..35  USED *)
865                                                   (* XI  ==>  INDEX REGISTER *)
866                                                   (* NXREG   NO MODIFIER *)
867       inxbloc : regpt ;                           (* POINTS BOX DESCRIBING INXREG *)
868       inxmem : integer ;                          (* BYTES DISPLACEMENT/PR6 OF A STORAGE WORD *)
869                                                   (* CONT. IN BITS 18..35 A WORD OFFSET SIGNED *)
870       inxmemrw : boolean ;                        (* TRUE IF INXMEM CAN BE WRITTEN *)
871       access : attraccess ;
872 
873 (* DIRECT ITEM=[[BASIS]+[INDEX]+DPLMT+[INXMEM]] BASIS=PR4/PR6
874    POINTEE   SAME BUT BASIS= ANY POINTER REGISTER
875    POINTABLE ITEM=[[[BASIS]+ITSDPLMT]+[INDEX]+DPLMT+[INXMEM]]
876    ENCODE    ITEM GENERATEA IN CODE *)
877       itsdplmt : integer ;                        (* BYTES DISP OF AN ITS EVEN BOUNDARY *)
878       pckd : boolean ;                            (* TRUE IF CONTAINING STRUCTURE WAS PACKED *)
879       nameaddr : ctp ;                            (* PTR TO NAME OF CONCERNED VAR OR FIELD *)
880       descreg : preg ;                            (* PTR TO DESCRIPTOR *)
881       descbloc : regpt ;                          (* BOX FOR THIS POINTER *)
882       vmo : boolean ; (* TRUE IF INTERNAL VAR OF MONITOR OR MODULE ACCESS BY PR5 *) { Inserted for SimOne }
883       temporary : boolean ;                       (* TRUE IF THIS VARIABLE IS THE RESULT OF AN EXPRESSION,
884                                                      ALLOCATED IN STACK (USED FOR RESULT OF STRING EXPRESSIONS *)
885       ) ;                                         (* END VARBL *)
886 
887     lval : (                                      (* ITEM IS LOADED IN A *)
888                                                   (* REGISTER RA,RQ,RAQ,REAQ,PSR *)
889       ldreg : register ;                          (* LOADED REGISTER *)
890       ldregbloc : regpt ;                         (* POINTS THE BOX DESCRIBING LDREG *)
891       psrsize : integer ;                         (* SIZE MEANINGSFULL IN BYTES OF PSR IF LOADED *)
892       ) ;                                         (* END LVAL *)
893 
894     chain : (                                     (* ITEM DESCRIBED IS A CHARACTER STRING CONSTANT *)
895                                                   (* GENERATED AT THE END OF CODE *)
896                                                   (* (WORD BOUNDARY ALIGNED) *)
897       alfactp : ctp ;                             (* POINTS THE (KONST,ALFACONST) BOX ASSOCIATED *)
898       ) ;                                         (* END CHAIN *)
899 
900     sval : (                                      (* ITEM DESCRIBED IS A COMPUTABLE VALUE *)
901                                                   (* BY THE COMPILER *)
902       val : integer ;                             (* WORD CONSTANT *)
903       rsval : real ;                              (* FLOAT CONSTANT *)
904       valpw : setarray ;                          (* SET CONSTANT *)
905       longv : integer ;                           (* BYTES LENGTH MEANINGSFULL IN VALPW *)
906       ) ;                                         (* END SVAL *)
907 
908     lcond : (                                     (* ITED DESCRIBED IS A BOOLEAN EITHER LOADED OR *)
909                                                   (* KNOWN ONLY BY THE SETTING OF INDICATORD *)
910       accbloc : regpt ;                           (* POINTS BOX DESCRIBING RA IF USED *)
911       accbool : boolean ;                         (* TRUE  <==> RA IS USED TO KEEP LCOND *)
912       transf : integer ;                          (* GIVES THE SUITABLE INDICATORS TESTING *)
913       ) ;                                         (* END LCOND *)
914 
915   END ;                                           (* RECORD ATTR *)
916 
917   typepr = (epp, spri, lprp) ;                    (*  FOR  PR. INST *)
918   typix = (adlx, adx, sxl, lxl) ;                 (*  FOR  XI  INST *)
919   typeofop = (load, sub, shiftl, add, neg, cmp, stor) ; (*  FOR  A,Q,AQ,EAQ INST *)
920   statearray = ARRAY [register] OF boolean ;      (* STATE OF REGISTERS *)
921 
922 (* STATEMENT MAP *)
923 
924   sttmapptr = @sttmap ;
925   sttmap = ARRAY [1..30000] OF
926   RECORD
927     word1 : integer ;
928     word2 : integer
929   END ;
930 
931 (* PROFILE COUNTERS AREA *)
932 
933   profareaptr = @profarea ;
934   profarea = ARRAY [0..60000] OF integer ;
935 
936 (* BLOCK NODE *)
937 
938   blocktype = (procblock, withblock) ;
939   vararea = (statics, locals) ;
940   blocknode = RECORD
941     father, brother, son : blocknodeptr ;         (* BLOCKS TREE *)
942     codebegin, codeend : integer ;                (* OFFSETS IN STATEMENT MAP *)
943     first : ctp ;                                 (* PTR TO FIRST DECLARED SYMBOL *)
944     CASE blocktp : blocktype OF
945     procblock : (
946       blockbox : ctp ;                            (* SYMBOL BLOCK FOR PROCEDURE *)
947       structureplace : integer ;                  (* OFFSET OF ENTRY STRUCTURE *)
948       firstlabel : labelblockptr ;                (* PTR TO FIRST LABEL *)
949       nextproc : blocknodeptr ;                   (* NEXT BLOCK *)
950       hdrfil, hdrind, hdrlen, hdrlin : integer ;  (* SOURCE OF HEADER *)
951       ) ;
952     withblock : (
953       wbase : vararea ;
954       wdispl : integer ;                          (* OFFSET *)
955       windirect : boolean ;
956       wstrfile, wstrindex, wstrlength : integer ;
957       recordptr : ctp ;
958       ) ;
959   END ;
960 
961 (* CONDITIONNAL COMPILATION MECHANISM *)
962 
963   condaddr = ^condbox ;
964   condbox = RECORD
965     condname : alfaid ;
966     nextcond : condaddr ;
967     active, activated, setinargs : boolean
968   END ;
969 
970 
971 (* ARRAY OF POINTERS TO USED NAMES - FOR "-list" OPTION *)
972 
973   usednamesarray = PACKED ARRAY [0..maxwseg] OF ctp ;
974   usednamesptr = @usednamesarray ;
975 
976 
977 (* END INCLUDE FILE CONSTTYPE.incl.pascal *)