OSDN Git Service

8584f33ab526a1d7a48228c10a96c39bddc814cd
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / cray_pointers_2.f90
1 ! { dg-do run }
2 ! { dg-options "-fcray-pointer -fbounds-check -fno-inline" }
3 !
4 ! Series of routines for testing a Cray pointer implementation
5 !
6 ! Note: Some of the test cases violate Fortran's alias rules;
7 ! the "-fno-inline option" for now prevents failures.
8 !
9 program craytest
10   common /errors/errors(400)
11   common /foo/foo ! To prevent optimizations
12   integer foo
13   integer i
14   logical errors
15   errors = .false.
16   foo = 0
17   call ptr1
18   call ptr2
19   call ptr3
20   call ptr4
21   call ptr5
22   call ptr6
23   call ptr7
24   call ptr8
25   call ptr9(9,10,11)
26   call ptr10(9,10,11)
27   call ptr11(9,10,11)
28   call ptr12(9,10,11)
29   call ptr13(9,10)
30   call parmtest
31 ! NOTE: Tests 1 through 12 were removed from this file
32 ! and placed in loc_1.f90, so we start at 13
33   do i=13,400
34      if (errors(i)) then
35 !        print *,"Test",i,"failed."
36         call abort()
37      endif
38   end do
39   if (foo.eq.0) then
40 !     print *,"Test did not run correctly."
41      call abort()
42   endif
43 end program craytest
44
45 ! ptr1 through ptr13 that Cray pointees are correctly used with
46 ! a variety of declaration styles
47 subroutine ptr1
48   common /errors/errors(400)
49   logical :: errors, intne, realne, chne, ch8ne
50   integer :: i,j,k
51   integer, parameter :: n = 9
52   integer, parameter :: m = 10
53   integer, parameter :: o = 11
54   integer itarg1 (n)
55   integer itarg2 (m,n)
56   integer itarg3 (o,m,n)
57   real rtarg1(n)
58   real rtarg2(m,n)
59   real rtarg3(o,m,n)
60   character chtarg1(n)
61   character chtarg2(m,n)
62   character chtarg3(o,m,n)
63   character*8 ch8targ1(n)
64   character*8 ch8targ2(m,n)
65   character*8 ch8targ3(o,m,n)
66   type drvd
67      real r1
68      integer i1
69      integer i2(5)
70   end type drvd
71   type(drvd) dtarg1(n)
72   type(drvd) dtarg2(m,n)
73   type(drvd) dtarg3(o,m,n)
74
75   type(drvd) dpte1(n)
76   type(drvd) dpte2(m,n)
77   type(drvd) dpte3(o,m,n)
78   integer ipte1 (n)
79   integer ipte2 (m,n)
80   integer ipte3 (o,m,n)
81   real rpte1(n)
82   real rpte2(m,n)
83   real rpte3(o,m,n)
84   character chpte1(n)
85   character chpte2(m,n)
86   character chpte3(o,m,n)
87   character*8 ch8pte1(n)
88   character*8 ch8pte2(m,n)
89   character*8 ch8pte3(o,m,n)
90
91   pointer(iptr1,dpte1)
92   pointer(iptr2,dpte2)
93   pointer(iptr3,dpte3)
94   pointer(iptr4,ipte1)
95   pointer(iptr5,ipte2)
96   pointer(iptr6,ipte3)
97   pointer(iptr7,rpte1)
98   pointer(iptr8,rpte2)
99   pointer(iptr9,rpte3)
100   pointer(iptr10,chpte1)
101   pointer(iptr11,chpte2)
102   pointer(iptr12,chpte3)
103   pointer(iptr13,ch8pte1)
104   pointer(iptr14,ch8pte2)
105   pointer(iptr15,ch8pte3)
106
107   iptr1 = loc(dtarg1)
108   iptr2 = loc(dtarg2)
109   iptr3 = loc(dtarg3)
110   iptr4 = loc(itarg1)
111   iptr5 = loc(itarg2)
112   iptr6 = loc(itarg3)
113   iptr7 = loc(rtarg1)
114   iptr8 = loc(rtarg2)
115   iptr9 = loc(rtarg3)
116   iptr10= loc(chtarg1)
117   iptr11= loc(chtarg2)
118   iptr12= loc(chtarg3)
119   iptr13= loc(ch8targ1)
120   iptr14= loc(ch8targ2)
121   iptr15= loc(ch8targ3)
122
123
124   do, i=1,n
125      dpte1(i)%i1=i
126      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
127         ! Error #13
128         errors(13) = .true.
129      endif
130
131      dtarg1(i)%i1=2*dpte1(i)%i1
132      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
133         ! Error #14
134         errors(14) = .true.
135      endif
136
137      ipte1(i) = i
138      if (intne(ipte1(i), itarg1(i))) then
139         ! Error #15
140         errors(15) = .true.
141      endif
142
143      itarg1(i) = -ipte1(i)
144      if (intne(ipte1(i), itarg1(i))) then
145         ! Error #16
146         errors(16) = .true.
147      endif
148
149      rpte1(i) = i * 5.0
150      if (realne(rpte1(i), rtarg1(i))) then
151         ! Error #17
152         errors(17) = .true.
153      endif
154
155      rtarg1(i) = i * (-5.0)
156      if (realne(rpte1(i), rtarg1(i))) then
157         ! Error #18
158         errors(18) = .true.
159      endif
160
161      chpte1(i) = 'a'
162      if (chne(chpte1(i), chtarg1(i))) then
163         ! Error #19
164         errors(19) = .true.
165      endif
166
167      chtarg1(i) = 'z'
168      if (chne(chpte1(i), chtarg1(i))) then
169         ! Error #20
170         errors(20) = .true.
171      endif
172
173      ch8pte1(i) = 'aaaaaaaa'
174      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
175         ! Error #21
176         errors(21) = .true.
177      endif
178
179      ch8targ1(i) = 'zzzzzzzz'
180      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
181         ! Error #22
182         errors(22) = .true.
183      endif
184
185      do, j=1,m
186         dpte2(j,i)%r1=1.0
187         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
188            ! Error #23
189            errors(23) = .true.
190         endif
191
192         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
193         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
194            ! Error #24
195            errors(24) = .true.
196         endif
197
198         ipte2(j,i) = i
199         if (intne(ipte2(j,i), itarg2(j,i))) then
200            ! Error #25
201            errors(25) = .true.
202         endif
203
204         itarg2(j,i) = -ipte2(j,i)
205         if (intne(ipte2(j,i), itarg2(j,i))) then
206            ! Error #26
207            errors(26) = .true.
208         endif
209
210         rpte2(j,i) = i * (-2.0)
211         if (realne(rpte2(j,i), rtarg2(j,i))) then
212            ! Error #27
213            errors(27) = .true.
214         endif
215
216         rtarg2(j,i) = i * (-3.0)
217         if (realne(rpte2(j,i), rtarg2(j,i))) then
218            ! Error #28
219            errors(28) = .true.
220         endif
221
222         chpte2(j,i) = 'a'
223         if (chne(chpte2(j,i), chtarg2(j,i))) then
224            ! Error #29
225            errors(29) = .true.
226         endif
227
228         chtarg2(j,i) = 'z'
229         if (chne(chpte2(j,i), chtarg2(j,i))) then
230            ! Error #30
231            errors(30) = .true.
232         endif
233
234         ch8pte2(j,i) = 'aaaaaaaa'
235         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
236            ! Error #31
237            errors(31) = .true.
238         endif
239
240         ch8targ2(j,i) = 'zzzzzzzz'
241         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
242            ! Error #32
243            errors(32) = .true.
244         endif
245         do k=1,o
246            dpte3(k,j,i)%i2(1+mod(i,5))=i
247            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
248                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
249               ! Error #33
250               errors(33) = .true.
251            endif
252
253            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
254            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
255                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
256               ! Error #34
257               errors(34) = .true.
258            endif
259
260            ipte3(k,j,i) = i
261            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
262               ! Error #35
263               errors(35) = .true.
264            endif
265
266            itarg3(k,j,i) = -ipte3(k,j,i)
267            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
268               ! Error #36
269               errors(36) = .true.
270            endif
271
272            rpte3(k,j,i) = i * 2.0
273            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
274               ! Error #37
275               errors(37) = .true.
276            endif
277
278            rtarg3(k,j,i) = i * 3.0
279            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
280               ! Error #38
281               errors(38) = .true.
282            endif
283
284            chpte3(k,j,i) = 'a'
285            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
286               ! Error #39
287               errors(39) = .true.
288            endif
289
290            chtarg3(k,j,i) = 'z'
291            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
292               ! Error #40
293               errors(40) = .true.
294            endif
295
296            ch8pte3(k,j,i) = 'aaaaaaaa'
297            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
298               ! Error #41
299               errors(41) = .true.
300            endif
301
302            ch8targ3(k,j,i) = 'zzzzzzzz'
303            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
304               ! Error #42
305               errors(42) = .true.
306            endif
307         end do
308      end do
309   end do
310
311   rtarg3 = .5
312   ! Vector syntax
313   do, i=1,n
314      ipte3 = i
315      rpte3 = rpte3+1
316      do, j=1,m
317         do k=1,o
318            if (intne(itarg3(k,j,i), i)) then
319               ! Error #43
320               errors(43) = .true.
321            endif
322
323            if (realne(rtarg3(k,j,i), i+.5)) then
324               ! Error #44
325               errors(44) = .true.
326            endif
327         end do
328      end do
329   end do
330
331 end subroutine ptr1
332
333
334 subroutine ptr2
335   common /errors/errors(400)
336   logical :: errors, intne, realne, chne, ch8ne
337   integer :: i,j,k
338   integer, parameter :: n = 9
339   integer, parameter :: m = 10
340   integer, parameter :: o = 11
341   integer itarg1 (n)
342   integer itarg2 (m,n)
343   integer itarg3 (o,m,n)
344   real rtarg1(n)
345   real rtarg2(m,n)
346   real rtarg3(o,m,n)
347   character chtarg1(n)
348   character chtarg2(m,n)
349   character chtarg3(o,m,n)
350   character*8 ch8targ1(n)
351   character*8 ch8targ2(m,n)
352   character*8 ch8targ3(o,m,n)
353   type drvd
354      real r1
355      integer i1
356      integer i2(5)
357   end type drvd
358   type(drvd) dtarg1(n)
359   type(drvd) dtarg2(m,n)
360   type(drvd) dtarg3(o,m,n)
361
362   type(drvd) dpte1
363   type(drvd) dpte2
364   type(drvd) dpte3
365   integer ipte1
366   integer ipte2
367   integer ipte3
368   real rpte1
369   real rpte2
370   real rpte3
371   character chpte1
372   character chpte2
373   character chpte3
374   character*8 ch8pte1
375   character*8 ch8pte2
376   character*8 ch8pte3
377
378   pointer(iptr1,dpte1(n))
379   pointer(iptr2,dpte2(m,n))
380   pointer(iptr3,dpte3(o,m,n))
381   pointer(iptr4,ipte1(n))
382   pointer(iptr5,ipte2 (m,n))
383   pointer(iptr6,ipte3(o,m,n))
384   pointer(iptr7,rpte1(n))
385   pointer(iptr8,rpte2(m,n))
386   pointer(iptr9,rpte3(o,m,n))
387   pointer(iptr10,chpte1(n))
388   pointer(iptr11,chpte2(m,n))
389   pointer(iptr12,chpte3(o,m,n))
390   pointer(iptr13,ch8pte1(n))
391   pointer(iptr14,ch8pte2(m,n))
392   pointer(iptr15,ch8pte3(o,m,n))
393
394   iptr1 = loc(dtarg1)
395   iptr2 = loc(dtarg2)
396   iptr3 = loc(dtarg3)
397   iptr4 = loc(itarg1)
398   iptr5 = loc(itarg2)
399   iptr6 = loc(itarg3)
400   iptr7 = loc(rtarg1)
401   iptr8 = loc(rtarg2)
402   iptr9 = loc(rtarg3)
403   iptr10= loc(chtarg1)
404   iptr11= loc(chtarg2)
405   iptr12= loc(chtarg3)
406   iptr13= loc(ch8targ1)
407   iptr14= loc(ch8targ2)
408   iptr15= loc(ch8targ3)
409
410   do, i=1,n
411      dpte1(i)%i1=i
412      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
413         ! Error #45
414         errors(45) = .true.
415      endif
416
417      dtarg1(i)%i1=2*dpte1(i)%i1
418      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
419         ! Error #46
420         errors(46) = .true.
421      endif
422
423      ipte1(i) = i
424      if (intne(ipte1(i), itarg1(i))) then
425         ! Error #47
426         errors(47) = .true.
427      endif
428
429      itarg1(i) = -ipte1(i)
430      if (intne(ipte1(i), itarg1(i))) then
431         ! Error #48
432         errors(48) = .true.
433      endif
434
435      rpte1(i) = i * 5.0
436      if (realne(rpte1(i), rtarg1(i))) then
437         ! Error #49
438         errors(49) = .true.
439      endif
440
441      rtarg1(i) = i * (-5.0)
442      if (realne(rpte1(i), rtarg1(i))) then
443         ! Error #50
444         errors(50) = .true.
445      endif
446
447      chpte1(i) = 'a'
448      if (chne(chpte1(i), chtarg1(i))) then
449         ! Error #51
450         errors(51) = .true.
451      endif
452
453      chtarg1(i) = 'z'
454      if (chne(chpte1(i), chtarg1(i))) then
455         ! Error #52
456         errors(52) = .true.
457      endif
458
459      ch8pte1(i) = 'aaaaaaaa'
460      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
461         ! Error #53
462         errors(53) = .true.
463      endif
464
465      ch8targ1(i) = 'zzzzzzzz'
466      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
467         ! Error #54
468         errors(54) = .true.
469      endif
470
471      do, j=1,m
472         dpte2(j,i)%r1=1.0
473         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
474            ! Error #55
475            errors(55) = .true.
476         endif
477
478         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
479         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
480            ! Error #56
481            errors(56) = .true.
482         endif
483
484         ipte2(j,i) = i
485         if (intne(ipte2(j,i), itarg2(j,i))) then
486            ! Error #57
487            errors(57) = .true.
488         endif
489
490         itarg2(j,i) = -ipte2(j,i)
491         if (intne(ipte2(j,i), itarg2(j,i))) then
492            ! Error #58
493            errors(58) = .true.
494         endif
495
496         rpte2(j,i) = i * (-2.0)
497         if (realne(rpte2(j,i), rtarg2(j,i))) then
498            ! Error #59
499            errors(59) = .true.
500         endif
501
502         rtarg2(j,i) = i * (-3.0)
503         if (realne(rpte2(j,i), rtarg2(j,i))) then
504            ! Error #60
505            errors(60) = .true.
506         endif
507
508         chpte2(j,i) = 'a'
509         if (chne(chpte2(j,i), chtarg2(j,i))) then
510            ! Error #61
511            errors(61) = .true.
512         endif
513
514         chtarg2(j,i) = 'z'
515         if (chne(chpte2(j,i), chtarg2(j,i))) then
516            ! Error #62
517            errors(62) = .true.
518         endif
519
520         ch8pte2(j,i) = 'aaaaaaaa'
521         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
522            ! Error #63
523            errors(63) = .true.
524         endif
525
526         ch8targ2(j,i) = 'zzzzzzzz'
527         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
528            ! Error #64
529            errors(64) = .true.
530         endif
531         do k=1,o
532            dpte3(k,j,i)%i2(1+mod(i,5))=i
533            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), dtarg3(k,j,i)%i2(1+mod(i,5)))) then
534               ! Error #65
535               errors(65) = .true.
536            endif
537
538            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
539            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), dtarg3(k,j,i)%i2(1+mod(i,5)))) then
540               ! Error #66
541               errors(66) = .true.
542            endif
543
544            ipte3(k,j,i) = i
545            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
546               ! Error #67
547               errors(67) = .true.
548            endif
549
550            itarg3(k,j,i) = -ipte3(k,j,i)
551            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
552               ! Error #68
553               errors(68) = .true.
554            endif
555
556            rpte3(k,j,i) = i * 2.0
557            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
558               ! Error #69
559               errors(69) = .true.
560            endif
561
562            rtarg3(k,j,i) = i * 3.0
563            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
564               ! Error #70
565               errors(70) = .true.
566            endif
567
568            chpte3(k,j,i) = 'a'
569            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
570               ! Error #71
571               errors(71) = .true.
572            endif
573
574            chtarg3(k,j,i) = 'z'
575            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
576               ! Error #72
577               errors(72) = .true.
578            endif
579
580            ch8pte3(k,j,i) = 'aaaaaaaa'
581            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
582               ! Error #73
583               errors(73) = .true.
584            endif
585
586            ch8targ3(k,j,i) = 'zzzzzzzz'
587            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
588               ! Error #74
589               errors(74) = .true.
590            endif
591         end do
592      end do
593   end do
594
595   rtarg3 = .5
596   ! Vector syntax
597   do, i=1,n
598      ipte3 = i
599      rpte3 = rpte3+1
600      do, j=1,m
601         do k=1,o
602            if (intne(itarg3(k,j,i), i)) then
603               ! Error #75
604               errors(75) = .true.
605            endif
606
607            if (realne(rtarg3(k,j,i), i+.5)) then
608               ! Error #76
609               errors(76) = .true.
610            endif
611         end do
612      end do
613   end do
614 end subroutine ptr2
615
616 subroutine ptr3
617   common /errors/errors(400)
618   logical :: errors, intne, realne, chne, ch8ne
619   integer :: i,j,k
620   integer, parameter :: n = 9
621   integer, parameter :: m = 10
622   integer, parameter :: o = 11
623   integer itarg1 (n)
624   integer itarg2 (m,n)
625   integer itarg3 (o,m,n)
626   real rtarg1(n)
627   real rtarg2(m,n)
628   real rtarg3(o,m,n)
629   character chtarg1(n)
630   character chtarg2(m,n)
631   character chtarg3(o,m,n)
632   character*8 ch8targ1(n)
633   character*8 ch8targ2(m,n)
634   character*8 ch8targ3(o,m,n)
635   type drvd
636      real r1
637      integer i1
638      integer i2(5)
639   end type drvd
640   type(drvd) dtarg1(n)
641   type(drvd) dtarg2(m,n)
642   type(drvd) dtarg3(o,m,n)
643
644   pointer(iptr1,dpte1(n))
645   pointer(iptr2,dpte2(m,n))
646   pointer(iptr3,dpte3(o,m,n))
647   pointer(iptr4,ipte1(n))
648   pointer(iptr5,ipte2 (m,n))
649   pointer(iptr6,ipte3(o,m,n))
650   pointer(iptr7,rpte1(n))
651   pointer(iptr8,rpte2(m,n))
652   pointer(iptr9,rpte3(o,m,n))
653   pointer(iptr10,chpte1(n))
654   pointer(iptr11,chpte2(m,n))
655   pointer(iptr12,chpte3(o,m,n))
656   pointer(iptr13,ch8pte1(n))
657   pointer(iptr14,ch8pte2(m,n))
658   pointer(iptr15,ch8pte3(o,m,n))
659
660   type(drvd) dpte1
661   type(drvd) dpte2
662   type(drvd) dpte3
663   integer ipte1
664   integer ipte2
665   integer ipte3
666   real rpte1
667   real rpte2
668   real rpte3
669   character chpte1
670   character chpte2
671   character chpte3
672   character*8 ch8pte1
673   character*8 ch8pte2
674   character*8 ch8pte3
675
676   iptr1 = loc(dtarg1)
677   iptr2 = loc(dtarg2)
678   iptr3 = loc(dtarg3)
679   iptr4 = loc(itarg1)
680   iptr5 = loc(itarg2)
681   iptr6 = loc(itarg3)
682   iptr7 = loc(rtarg1)
683   iptr8 = loc(rtarg2)
684   iptr9 = loc(rtarg3)
685   iptr10= loc(chtarg1)
686   iptr11= loc(chtarg2)
687   iptr12= loc(chtarg3)
688   iptr13= loc(ch8targ1)
689   iptr14= loc(ch8targ2)
690   iptr15= loc(ch8targ3)
691
692   do, i=1,n
693      dpte1(i)%i1=i
694      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
695         ! Error #77
696         errors(77) = .true.
697      endif
698
699      dtarg1(i)%i1=2*dpte1(i)%i1
700      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
701         ! Error #78
702         errors(78) = .true.
703      endif
704
705      ipte1(i) = i
706      if (intne(ipte1(i), itarg1(i))) then
707         ! Error #79
708         errors(79) = .true.
709      endif
710
711      itarg1(i) = -ipte1(i)
712      if (intne(ipte1(i), itarg1(i))) then
713         ! Error #80
714         errors(80) = .true.
715      endif
716
717      rpte1(i) = i * 5.0
718      if (realne(rpte1(i), rtarg1(i))) then
719         ! Error #81
720         errors(81) = .true.
721      endif
722
723      rtarg1(i) = i * (-5.0)
724      if (realne(rpte1(i), rtarg1(i))) then
725         ! Error #82
726         errors(82) = .true.
727      endif
728
729      chpte1(i) = 'a'
730      if (chne(chpte1(i), chtarg1(i))) then
731         ! Error #83
732         errors(83) = .true.
733      endif
734
735      chtarg1(i) = 'z'
736      if (chne(chpte1(i), chtarg1(i))) then
737         ! Error #84
738         errors(84) = .true.
739      endif
740
741      ch8pte1(i) = 'aaaaaaaa'
742      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
743         ! Error #85
744         errors(85) = .true.
745      endif
746
747      ch8targ1(i) = 'zzzzzzzz'
748      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
749         ! Error #86
750         errors(86) = .true.
751      endif
752
753      do, j=1,m
754         dpte2(j,i)%r1=1.0
755         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
756            ! Error #87
757            errors(87) = .true.
758         endif
759
760         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
761         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
762            ! Error #88
763            errors(88) = .true.
764         endif
765
766         ipte2(j,i) = i
767         if (intne(ipte2(j,i), itarg2(j,i))) then
768            ! Error #89
769            errors(89) = .true.
770         endif
771
772         itarg2(j,i) = -ipte2(j,i)
773         if (intne(ipte2(j,i), itarg2(j,i))) then
774            ! Error #90
775            errors(90) = .true.
776         endif
777
778         rpte2(j,i) = i * (-2.0)
779         if (realne(rpte2(j,i), rtarg2(j,i))) then
780            ! Error #91
781            errors(91) = .true.
782         endif
783
784         rtarg2(j,i) = i * (-3.0)
785         if (realne(rpte2(j,i), rtarg2(j,i))) then
786            ! Error #92
787            errors(92) = .true.
788         endif
789
790         chpte2(j,i) = 'a'
791         if (chne(chpte2(j,i), chtarg2(j,i))) then
792            ! Error #93
793            errors(93) = .true.
794         endif
795
796         chtarg2(j,i) = 'z'
797         if (chne(chpte2(j,i), chtarg2(j,i))) then
798            ! Error #94
799            errors(94) = .true.
800         endif
801
802         ch8pte2(j,i) = 'aaaaaaaa'
803         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
804            ! Error #95
805            errors(95) = .true.
806         endif
807
808         ch8targ2(j,i) = 'zzzzzzzz'
809         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
810            ! Error #96
811            errors(96) = .true.
812         endif
813         do k=1,o
814            dpte3(k,j,i)%i2(1+mod(i,5))=i
815            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
816                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
817               ! Error #97
818               errors(97) = .true.
819            endif
820
821            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
822            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
823                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
824               ! Error #98
825               errors(98) = .true.
826            endif
827
828            ipte3(k,j,i) = i
829            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
830               ! Error #99
831               errors(99) = .true.
832            endif
833
834            itarg3(k,j,i) = -ipte3(k,j,i)
835            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
836               ! Error #100
837               errors(100) = .true.
838            endif
839
840            rpte3(k,j,i) = i * 2.0
841            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
842               ! Error #101
843               errors(101) = .true.
844            endif
845
846            rtarg3(k,j,i) = i * 3.0
847            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
848               ! Error #102
849               errors(102) = .true.
850            endif
851
852            chpte3(k,j,i) = 'a'
853            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
854               ! Error #103
855               errors(103) = .true.
856            endif
857
858            chtarg3(k,j,i) = 'z'
859            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
860               ! Error #104
861               errors(104) = .true.
862            endif
863
864            ch8pte3(k,j,i) = 'aaaaaaaa'
865            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
866               ! Error #105
867               errors(105) = .true.
868            endif
869
870            ch8targ3(k,j,i) = 'zzzzzzzz'
871            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
872               ! Error #106
873               errors(106) = .true.
874            endif
875         end do
876      end do
877   end do
878
879   rtarg3 = .5
880   ! Vector syntax
881   do, i=1,n
882      ipte3 = i
883      rpte3 = rpte3+1
884      do, j=1,m
885         do k=1,o
886            if (intne(itarg3(k,j,i), i)) then
887               ! Error #107
888               errors(107) = .true.
889            endif
890
891            if (realne(rtarg3(k,j,i), i+.5)) then
892               ! Error #108
893               errors(108) = .true.
894            endif
895         end do
896      end do
897   end do
898 end subroutine ptr3
899
900 subroutine ptr4
901   common /errors/errors(400)
902   logical :: errors, intne, realne, chne, ch8ne
903   integer :: i,j,k
904   integer, parameter :: n = 9
905   integer, parameter :: m = 10
906   integer, parameter :: o = 11
907   integer itarg1 (n)
908   integer itarg2 (m,n)
909   integer itarg3 (o,m,n)
910   real rtarg1(n)
911   real rtarg2(m,n)
912   real rtarg3(o,m,n)
913   character chtarg1(n)
914   character chtarg2(m,n)
915   character chtarg3(o,m,n)
916   character*8 ch8targ1(n)
917   character*8 ch8targ2(m,n)
918   character*8 ch8targ3(o,m,n)
919   type drvd
920      real r1
921      integer i1
922      integer i2(5)
923   end type drvd
924   type(drvd) dtarg1(n)
925   type(drvd) dtarg2(m,n)
926   type(drvd) dtarg3(o,m,n)
927
928   pointer(iptr1,dpte1),(iptr2,dpte2),(iptr3,dpte3)
929   pointer    (iptr4,ipte1),  (iptr5,ipte2) ,(iptr6,ipte3),(iptr7,rpte1)
930   pointer(iptr8,rpte2)
931   pointer(iptr9,rpte3),(iptr10,chpte1)
932   pointer(iptr11,chpte2),(iptr12,chpte3),(iptr13,ch8pte1)
933   pointer(iptr14,ch8pte2)
934   pointer(iptr15,ch8pte3)
935
936   type(drvd) dpte1(n)
937   type(drvd) dpte2(m,n)
938   type(drvd) dpte3(o,m,n)
939   integer ipte1 (n)
940   integer ipte2 (m,n)
941   integer ipte3 (o,m,n)
942   real rpte1(n)
943   real rpte2(m,n)
944   real rpte3(o,m,n)
945   character chpte1(n)
946   character chpte2(m,n)
947   character chpte3(o,m,n)
948   character*8 ch8pte1(n)
949   character*8 ch8pte2(m,n)
950   character*8 ch8pte3(o,m,n)
951
952   iptr1 = loc(dtarg1)
953   iptr2 = loc(dtarg2)
954   iptr3 = loc(dtarg3)
955   iptr4 = loc(itarg1)
956   iptr5 = loc(itarg2)
957   iptr6 = loc(itarg3)
958   iptr7 = loc(rtarg1)
959   iptr8 = loc(rtarg2)
960   iptr9 = loc(rtarg3)
961   iptr10= loc(chtarg1)
962   iptr11= loc(chtarg2)
963   iptr12= loc(chtarg3)
964   iptr13= loc(ch8targ1)
965   iptr14= loc(ch8targ2)
966   iptr15= loc(ch8targ3)
967
968
969   do, i=1,n
970      dpte1(i)%i1=i
971      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
972         ! Error #109
973         errors(109) = .true.
974      endif
975
976      dtarg1(i)%i1=2*dpte1(i)%i1
977      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
978         ! Error #110
979         errors(110) = .true.
980      endif
981
982      ipte1(i) = i
983      if (intne(ipte1(i), itarg1(i))) then
984         ! Error #111
985         errors(111) = .true.
986      endif
987
988      itarg1(i) = -ipte1(i)
989      if (intne(ipte1(i), itarg1(i))) then
990         ! Error #112
991         errors(112) = .true.
992      endif
993
994      rpte1(i) = i * 5.0
995      if (realne(rpte1(i), rtarg1(i))) then
996         ! Error #113
997         errors(113) = .true.
998      endif
999
1000      rtarg1(i) = i * (-5.0)
1001      if (realne(rpte1(i), rtarg1(i))) then
1002         ! Error #114
1003         errors(114) = .true.
1004      endif
1005
1006      chpte1(i) = 'a'
1007      if (chne(chpte1(i), chtarg1(i))) then
1008         ! Error #115
1009         errors(115) = .true.
1010      endif
1011
1012      chtarg1(i) = 'z'
1013      if (chne(chpte1(i), chtarg1(i))) then
1014         ! Error #116
1015         errors(116) = .true.
1016      endif
1017
1018      ch8pte1(i) = 'aaaaaaaa'
1019      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1020         ! Error #117
1021         errors(117) = .true.
1022      endif
1023
1024      ch8targ1(i) = 'zzzzzzzz'
1025      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1026         ! Error #118
1027         errors(118) = .true.
1028      endif
1029
1030      do, j=1,m
1031         dpte2(j,i)%r1=1.0
1032         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1033            ! Error #119
1034            errors(119) = .true.
1035         endif
1036
1037         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
1038         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1039            ! Error #120
1040            errors(120) = .true.
1041         endif
1042
1043         ipte2(j,i) = i
1044         if (intne(ipte2(j,i), itarg2(j,i))) then
1045            ! Error #121
1046            errors(121) = .true.
1047         endif
1048
1049         itarg2(j,i) = -ipte2(j,i)
1050         if (intne(ipte2(j,i), itarg2(j,i))) then
1051            ! Error #122
1052            errors(122) = .true.
1053         endif
1054
1055         rpte2(j,i) = i * (-2.0)
1056         if (realne(rpte2(j,i), rtarg2(j,i))) then
1057            ! Error #123
1058            errors(123) = .true.
1059         endif
1060
1061         rtarg2(j,i) = i * (-3.0)
1062         if (realne(rpte2(j,i), rtarg2(j,i))) then
1063            ! Error #124
1064            errors(124) = .true.
1065         endif
1066
1067         chpte2(j,i) = 'a'
1068         if (chne(chpte2(j,i), chtarg2(j,i))) then
1069            ! Error #125
1070            errors(125) = .true.
1071         endif
1072
1073         chtarg2(j,i) = 'z'
1074         if (chne(chpte2(j,i), chtarg2(j,i))) then
1075            ! Error #126
1076            errors(126) = .true.
1077         endif
1078
1079         ch8pte2(j,i) = 'aaaaaaaa'
1080         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1081            ! Error #127
1082            errors(127) = .true.
1083         endif
1084
1085         ch8targ2(j,i) = 'zzzzzzzz'
1086         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1087            ! Error #128
1088            errors(128) = .true.
1089         endif
1090         do k=1,o
1091            dpte3(k,j,i)%i2(1+mod(i,5))=i
1092            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1093                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1094               ! Error #129
1095               errors(129) = .true.
1096            endif
1097
1098            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
1099            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1100                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1101               ! Error #130
1102               errors(130) = .true.
1103            endif
1104
1105            ipte3(k,j,i) = i
1106            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1107               ! Error #131
1108               errors(131) = .true.
1109            endif
1110
1111            itarg3(k,j,i) = -ipte3(k,j,i)
1112            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1113               ! Error #132
1114               errors(132) = .true.
1115            endif
1116
1117            rpte3(k,j,i) = i * 2.0
1118            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1119               ! Error #133
1120               errors(133) = .true.
1121            endif
1122
1123            rtarg3(k,j,i) = i * 3.0
1124            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1125               ! Error #134
1126               errors(134) = .true.
1127            endif
1128
1129            chpte3(k,j,i) = 'a'
1130            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1131               ! Error #135
1132               errors(135) = .true.
1133            endif
1134
1135            chtarg3(k,j,i) = 'z'
1136            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1137               ! Error #136
1138               errors(136) = .true.
1139            endif
1140
1141            ch8pte3(k,j,i) = 'aaaaaaaa'
1142            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1143               ! Error #137
1144               errors(137) = .true.
1145            endif
1146
1147            ch8targ3(k,j,i) = 'zzzzzzzz'
1148            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1149               ! Error #138
1150               errors(138) = .true.
1151            endif
1152         end do
1153      end do
1154   end do
1155
1156   rtarg3 = .5
1157   ! Vector syntax
1158   do, i=1,n
1159      ipte3 = i
1160      rpte3 = rpte3+1
1161      do, j=1,m
1162         do k=1,o
1163            if (intne(itarg3(k,j,i), i)) then
1164               ! Error #139
1165               errors(139) = .true.
1166            endif
1167
1168            if (realne(rtarg3(k,j,i), i+.5)) then
1169               ! Error #140
1170               errors(140) = .true.
1171            endif
1172         end do
1173      end do
1174   end do
1175
1176 end subroutine ptr4
1177
1178 subroutine ptr5
1179   common /errors/errors(400)
1180   logical :: errors, intne, realne, chne, ch8ne
1181   integer :: i,j,k
1182   integer, parameter :: n = 9
1183   integer, parameter :: m = 10
1184   integer, parameter :: o = 11
1185   integer itarg1 (n)
1186   integer itarg2 (m,n)
1187   integer itarg3 (o,m,n)
1188   real rtarg1(n)
1189   real rtarg2(m,n)
1190   real rtarg3(o,m,n)
1191   character chtarg1(n)
1192   character chtarg2(m,n)
1193   character chtarg3(o,m,n)
1194   character*8 ch8targ1(n)
1195   character*8 ch8targ2(m,n)
1196   character*8 ch8targ3(o,m,n)
1197   type drvd
1198      real r1
1199      integer i1
1200      integer i2(5)
1201   end type drvd
1202   type(drvd) dtarg1(n)
1203   type(drvd) dtarg2(m,n)
1204   type(drvd) dtarg3(o,m,n)
1205
1206   type(drvd) dpte1(*)
1207   type(drvd) dpte2(m,*)
1208   type(drvd) dpte3(o,m,*)
1209   integer ipte1 (*)
1210   integer ipte2 (m,*)
1211   integer ipte3 (o,m,*)
1212   real rpte1(*)
1213   real rpte2(m,*)
1214   real rpte3(o,m,*)
1215   character chpte1(*)
1216   character chpte2(m,*)
1217   character chpte3(o,m,*)
1218   character*8 ch8pte1(*)
1219   character*8 ch8pte2(m,*)
1220   character*8 ch8pte3(o,m,*)
1221
1222   pointer(iptr1,dpte1)
1223   pointer(iptr2,dpte2)
1224   pointer(iptr3,dpte3)
1225   pointer(iptr4,ipte1)
1226   pointer(iptr5,ipte2)
1227   pointer(iptr6,ipte3)
1228   pointer(iptr7,rpte1)
1229   pointer(iptr8,rpte2)
1230   pointer(iptr9,rpte3)
1231   pointer(iptr10,chpte1)
1232   pointer(iptr11,chpte2)
1233   pointer(iptr12,chpte3)
1234   pointer(iptr13,ch8pte1)
1235   pointer(iptr14,ch8pte2)
1236   pointer(iptr15,ch8pte3)
1237
1238   iptr1 = loc(dtarg1)
1239   iptr2 = loc(dtarg2)
1240   iptr3 = loc(dtarg3)
1241   iptr4 = loc(itarg1)
1242   iptr5 = loc(itarg2)
1243   iptr6 = loc(itarg3)
1244   iptr7 = loc(rtarg1)
1245   iptr8 = loc(rtarg2)
1246   iptr9 = loc(rtarg3)
1247   iptr10= loc(chtarg1)
1248   iptr11= loc(chtarg2)
1249   iptr12= loc(chtarg3)
1250   iptr13= loc(ch8targ1)
1251   iptr14= loc(ch8targ2)
1252   iptr15= loc(ch8targ3)
1253
1254
1255   do, i=1,n
1256      dpte1(i)%i1=i
1257      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1258         ! Error #141
1259         errors(141) = .true.
1260      endif
1261
1262      dtarg1(i)%i1=2*dpte1(i)%i1
1263      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1264         ! Error #142
1265         errors(142) = .true.
1266      endif
1267
1268      ipte1(i) = i
1269      if (intne(ipte1(i), itarg1(i))) then
1270         ! Error #143
1271         errors(143) = .true.
1272      endif
1273
1274      itarg1(i) = -ipte1(i)
1275      if (intne(ipte1(i), itarg1(i))) then
1276         ! Error #144
1277         errors(144) = .true.
1278      endif
1279
1280      rpte1(i) = i * 5.0
1281      if (realne(rpte1(i), rtarg1(i))) then
1282         ! Error #145
1283         errors(145) = .true.
1284      endif
1285
1286      rtarg1(i) = i * (-5.0)
1287      if (realne(rpte1(i), rtarg1(i))) then
1288         ! Error #146
1289         errors(146) = .true.
1290      endif
1291
1292      chpte1(i) = 'a'
1293      if (chne(chpte1(i), chtarg1(i))) then
1294         ! Error #147
1295         errors(147) = .true.
1296      endif
1297
1298      chtarg1(i) = 'z'
1299      if (chne(chpte1(i), chtarg1(i))) then
1300         ! Error #148
1301         errors(148) = .true.
1302      endif
1303
1304      ch8pte1(i) = 'aaaaaaaa'
1305      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1306         ! Error #149
1307         errors(149) = .true.
1308      endif
1309
1310      ch8targ1(i) = 'zzzzzzzz'
1311      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1312         ! Error #150
1313         errors(150) = .true.
1314      endif
1315
1316      do, j=1,m
1317         dpte2(j,i)%r1=1.0
1318         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1319            ! Error #151
1320            errors(151) = .true.
1321         endif
1322
1323         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
1324         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1325            ! Error #152
1326            errors(152) = .true.
1327         endif
1328
1329         ipte2(j,i) = i
1330         if (intne(ipte2(j,i), itarg2(j,i))) then
1331            ! Error #153
1332            errors(153) = .true.
1333         endif
1334
1335         itarg2(j,i) = -ipte2(j,i)
1336         if (intne(ipte2(j,i), itarg2(j,i))) then
1337            ! Error #154
1338            errors(154) = .true.
1339         endif
1340
1341         rpte2(j,i) = i * (-2.0)
1342         if (realne(rpte2(j,i), rtarg2(j,i))) then
1343            ! Error #155
1344            errors(155) = .true.
1345         endif
1346
1347         rtarg2(j,i) = i * (-3.0)
1348         if (realne(rpte2(j,i), rtarg2(j,i))) then
1349            ! Error #156
1350            errors(156) = .true.
1351         endif
1352
1353         chpte2(j,i) = 'a'
1354         if (chne(chpte2(j,i), chtarg2(j,i))) then
1355            ! Error #157
1356            errors(157) = .true.
1357         endif
1358
1359         chtarg2(j,i) = 'z'
1360         if (chne(chpte2(j,i), chtarg2(j,i))) then
1361            ! Error #158
1362            errors(158) = .true.
1363         endif
1364
1365         ch8pte2(j,i) = 'aaaaaaaa'
1366         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1367            ! Error #159
1368            errors(159) = .true.
1369         endif
1370
1371         ch8targ2(j,i) = 'zzzzzzzz'
1372         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1373            ! Error #160
1374            errors(160) = .true.
1375         endif
1376         do k=1,o
1377            dpte3(k,j,i)%i2(1+mod(i,5))=i
1378            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1379                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1380               ! Error #161
1381               errors(161) = .true.
1382            endif
1383
1384            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
1385            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1386                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1387               ! Error #162
1388               errors(162) = .true.
1389            endif
1390
1391            ipte3(k,j,i) = i
1392            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1393               ! Error #163
1394               errors(163) = .true.
1395            endif
1396
1397            itarg3(k,j,i) = -ipte3(k,j,i)
1398            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1399               ! Error #164
1400               errors(164) = .true.
1401            endif
1402
1403            rpte3(k,j,i) = i * 2.0
1404            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1405               ! Error #165
1406               errors(165) = .true.
1407            endif
1408
1409            rtarg3(k,j,i) = i * 3.0
1410            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1411               ! Error #166
1412               errors(166) = .true.
1413            endif
1414
1415            chpte3(k,j,i) = 'a'
1416            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1417               ! Error #167
1418               errors(167) = .true.
1419            endif
1420
1421            chtarg3(k,j,i) = 'z'
1422            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1423               ! Error #168
1424               errors(168) = .true.
1425            endif
1426
1427            ch8pte3(k,j,i) = 'aaaaaaaa'
1428            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1429               ! Error #169
1430               errors(169) = .true.
1431            endif
1432
1433            ch8targ3(k,j,i) = 'zzzzzzzz'
1434            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1435               ! Error #170
1436               errors(170) = .true.
1437            endif
1438         end do
1439      end do
1440   end do
1441
1442 end subroutine ptr5
1443
1444
1445 subroutine ptr6
1446   common /errors/errors(400)
1447   logical :: errors, intne, realne, chne, ch8ne
1448   integer :: i,j,k
1449   integer, parameter :: n = 9
1450   integer, parameter :: m = 10
1451   integer, parameter :: o = 11
1452   integer itarg1 (n)
1453   integer itarg2 (m,n)
1454   integer itarg3 (o,m,n)
1455   real rtarg1(n)
1456   real rtarg2(m,n)
1457   real rtarg3(o,m,n)
1458   character chtarg1(n)
1459   character chtarg2(m,n)
1460   character chtarg3(o,m,n)
1461   character*8 ch8targ1(n)
1462   character*8 ch8targ2(m,n)
1463   character*8 ch8targ3(o,m,n)
1464   type drvd
1465      real r1
1466      integer i1
1467      integer i2(5)
1468   end type drvd
1469   type(drvd) dtarg1(n)
1470   type(drvd) dtarg2(m,n)
1471   type(drvd) dtarg3(o,m,n)
1472
1473   type(drvd) dpte1
1474   type(drvd) dpte2
1475   type(drvd) dpte3
1476   integer ipte1
1477   integer ipte2
1478   integer ipte3
1479   real rpte1
1480   real rpte2
1481   real rpte3
1482   character chpte1
1483   character chpte2
1484   character chpte3
1485   character*8 ch8pte1
1486   character*8 ch8pte2
1487   character*8 ch8pte3
1488
1489   pointer(iptr1,dpte1(*))
1490   pointer(iptr2,dpte2(m,*))
1491   pointer(iptr3,dpte3(o,m,*))
1492   pointer(iptr4,ipte1(*))
1493   pointer(iptr5,ipte2 (m,*))
1494   pointer(iptr6,ipte3(o,m,*))
1495   pointer(iptr7,rpte1(*))
1496   pointer(iptr8,rpte2(m,*))
1497   pointer(iptr9,rpte3(o,m,*))
1498   pointer(iptr10,chpte1(*))
1499   pointer(iptr11,chpte2(m,*))
1500   pointer(iptr12,chpte3(o,m,*))
1501   pointer(iptr13,ch8pte1(*))
1502   pointer(iptr14,ch8pte2(m,*))
1503   pointer(iptr15,ch8pte3(o,m,*))
1504
1505   iptr1 = loc(dtarg1)
1506   iptr2 = loc(dtarg2)
1507   iptr3 = loc(dtarg3)
1508   iptr4 = loc(itarg1)
1509   iptr5 = loc(itarg2)
1510   iptr6 = loc(itarg3)
1511   iptr7 = loc(rtarg1)
1512   iptr8 = loc(rtarg2)
1513   iptr9 = loc(rtarg3)
1514   iptr10= loc(chtarg1)
1515   iptr11= loc(chtarg2)
1516   iptr12= loc(chtarg3)
1517   iptr13= loc(ch8targ1)
1518   iptr14= loc(ch8targ2)
1519   iptr15= loc(ch8targ3)
1520
1521   do, i=1,n
1522      dpte1(i)%i1=i
1523      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1524         ! Error #171
1525         errors(171) = .true.
1526      endif
1527
1528      dtarg1(i)%i1=2*dpte1(i)%i1
1529      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1530         ! Error #172
1531         errors(172) = .true.
1532      endif
1533
1534      ipte1(i) = i
1535      if (intne(ipte1(i), itarg1(i))) then
1536         ! Error #173
1537         errors(173) = .true.
1538      endif
1539
1540      itarg1(i) = -ipte1(i)
1541      if (intne(ipte1(i), itarg1(i))) then
1542         ! Error #174
1543         errors(174) = .true.
1544      endif
1545
1546      rpte1(i) = i * 5.0
1547      if (realne(rpte1(i), rtarg1(i))) then
1548         ! Error #175
1549         errors(175) = .true.
1550      endif
1551
1552      rtarg1(i) = i * (-5.0)
1553      if (realne(rpte1(i), rtarg1(i))) then
1554         ! Error #176
1555         errors(176) = .true.
1556      endif
1557
1558      chpte1(i) = 'a'
1559      if (chne(chpte1(i), chtarg1(i))) then
1560         ! Error #177
1561         errors(177) = .true.
1562      endif
1563
1564      chtarg1(i) = 'z'
1565      if (chne(chpte1(i), chtarg1(i))) then
1566         ! Error #178
1567         errors(178) = .true.
1568      endif
1569
1570      ch8pte1(i) = 'aaaaaaaa'
1571      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1572         ! Error #179
1573         errors(179) = .true.
1574      endif
1575
1576      ch8targ1(i) = 'zzzzzzzz'
1577      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1578         ! Error #180
1579         errors(180) = .true.
1580      endif
1581
1582      do, j=1,m
1583         dpte2(j,i)%r1=1.0
1584         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1585            ! Error #181
1586            errors(181) = .true.
1587         endif
1588
1589         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
1590         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1591            ! Error #182
1592            errors(182) = .true.
1593         endif
1594
1595         ipte2(j,i) = i
1596         if (intne(ipte2(j,i), itarg2(j,i))) then
1597            ! Error #183
1598            errors(183) = .true.
1599         endif
1600
1601         itarg2(j,i) = -ipte2(j,i)
1602         if (intne(ipte2(j,i), itarg2(j,i))) then
1603            ! Error #184
1604            errors(184) = .true.
1605         endif
1606
1607         rpte2(j,i) = i * (-2.0)
1608         if (realne(rpte2(j,i), rtarg2(j,i))) then
1609            ! Error #185
1610            errors(185) = .true.
1611         endif
1612
1613         rtarg2(j,i) = i * (-3.0)
1614         if (realne(rpte2(j,i), rtarg2(j,i))) then
1615            ! Error #186
1616            errors(186) = .true.
1617         endif
1618
1619         chpte2(j,i) = 'a'
1620         if (chne(chpte2(j,i), chtarg2(j,i))) then
1621            ! Error #187
1622            errors(187) = .true.
1623         endif
1624
1625         chtarg2(j,i) = 'z'
1626         if (chne(chpte2(j,i), chtarg2(j,i))) then
1627            ! Error #188
1628            errors(188) = .true.
1629         endif
1630
1631         ch8pte2(j,i) = 'aaaaaaaa'
1632         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1633            ! Error #189
1634            errors(189) = .true.
1635         endif
1636
1637         ch8targ2(j,i) = 'zzzzzzzz'
1638         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1639            ! Error #190
1640            errors(190) = .true.
1641         endif
1642         do k=1,o
1643            dpte3(k,j,i)%i2(1+mod(i,5))=i
1644            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1645                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1646               ! Error #191
1647               errors(191) = .true.
1648            endif
1649
1650            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
1651            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1652                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1653               ! Error #192
1654               errors(192) = .true.
1655            endif
1656
1657            ipte3(k,j,i) = i
1658            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1659               ! Error #193
1660               errors(193) = .true.
1661            endif
1662
1663            itarg3(k,j,i) = -ipte3(k,j,i)
1664            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1665               ! Error #194
1666               errors(194) = .true.
1667            endif
1668
1669            rpte3(k,j,i) = i * 2.0
1670            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1671               ! Error #195
1672               errors(195) = .true.
1673            endif
1674
1675            rtarg3(k,j,i) = i * 3.0
1676            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1677               ! Error #196
1678               errors(196) = .true.
1679            endif
1680
1681            chpte3(k,j,i) = 'a'
1682            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1683               ! Error #197
1684               errors(197) = .true.
1685            endif
1686
1687            chtarg3(k,j,i) = 'z'
1688            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1689               ! Error #198
1690               errors(198) = .true.
1691            endif
1692
1693            ch8pte3(k,j,i) = 'aaaaaaaa'
1694            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1695               ! Error #199
1696               errors(199) = .true.
1697            endif
1698
1699            ch8targ3(k,j,i) = 'zzzzzzzz'
1700            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1701               ! Error #200
1702               errors(200) = .true.
1703            endif
1704         end do
1705      end do
1706   end do
1707
1708 end subroutine ptr6
1709
1710 subroutine ptr7
1711   common /errors/errors(400)
1712   logical :: errors, intne, realne, chne, ch8ne
1713   integer :: i,j,k
1714   integer, parameter :: n = 9
1715   integer, parameter :: m = 10
1716   integer, parameter :: o = 11
1717   integer itarg1 (n)
1718   integer itarg2 (m,n)
1719   integer itarg3 (o,m,n)
1720   real rtarg1(n)
1721   real rtarg2(m,n)
1722   real rtarg3(o,m,n)
1723   character chtarg1(n)
1724   character chtarg2(m,n)
1725   character chtarg3(o,m,n)
1726   character*8 ch8targ1(n)
1727   character*8 ch8targ2(m,n)
1728   character*8 ch8targ3(o,m,n)
1729   type drvd
1730      real r1
1731      integer i1
1732      integer i2(5)
1733   end type drvd
1734   type(drvd) dtarg1(n)
1735   type(drvd) dtarg2(m,n)
1736   type(drvd) dtarg3(o,m,n)
1737
1738   pointer(iptr1,dpte1(*))
1739   pointer(iptr2,dpte2(m,*))
1740   pointer(iptr3,dpte3(o,m,*))
1741   pointer(iptr4,ipte1(*))
1742   pointer(iptr5,ipte2 (m,*))
1743   pointer(iptr6,ipte3(o,m,*))
1744   pointer(iptr7,rpte1(*))
1745   pointer(iptr8,rpte2(m,*))
1746   pointer(iptr9,rpte3(o,m,*))
1747   pointer(iptr10,chpte1(*))
1748   pointer(iptr11,chpte2(m,*))
1749   pointer(iptr12,chpte3(o,m,*))
1750   pointer(iptr13,ch8pte1(*))
1751   pointer(iptr14,ch8pte2(m,*))
1752   pointer(iptr15,ch8pte3(o,m,*))
1753
1754   type(drvd) dpte1
1755   type(drvd) dpte2
1756   type(drvd) dpte3
1757   integer ipte1
1758   integer ipte2
1759   integer ipte3
1760   real rpte1
1761   real rpte2
1762   real rpte3
1763   character chpte1
1764   character chpte2
1765   character chpte3
1766   character*8 ch8pte1
1767   character*8 ch8pte2
1768   character*8 ch8pte3
1769
1770   iptr1 = loc(dtarg1)
1771   iptr2 = loc(dtarg2)
1772   iptr3 = loc(dtarg3)
1773   iptr4 = loc(itarg1)
1774   iptr5 = loc(itarg2)
1775   iptr6 = loc(itarg3)
1776   iptr7 = loc(rtarg1)
1777   iptr8 = loc(rtarg2)
1778   iptr9 = loc(rtarg3)
1779   iptr10= loc(chtarg1)
1780   iptr11= loc(chtarg2)
1781   iptr12= loc(chtarg3)
1782   iptr13= loc(ch8targ1)
1783   iptr14= loc(ch8targ2)
1784   iptr15= loc(ch8targ3)
1785
1786   do, i=1,n
1787      dpte1(i)%i1=i
1788      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1789         ! Error #201
1790         errors(201) = .true.
1791      endif
1792
1793      dtarg1(i)%i1=2*dpte1(i)%i1
1794      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
1795         ! Error #202
1796         errors(202) = .true.
1797      endif
1798
1799      ipte1(i) = i
1800      if (intne(ipte1(i), itarg1(i))) then
1801         ! Error #203
1802         errors(203) = .true.
1803      endif
1804
1805      itarg1(i) = -ipte1(i)
1806      if (intne(ipte1(i), itarg1(i))) then
1807         ! Error #204
1808         errors(204) = .true.
1809      endif
1810
1811      rpte1(i) = i * 5.0
1812      if (realne(rpte1(i), rtarg1(i))) then
1813         ! Error #205
1814         errors(205) = .true.
1815      endif
1816
1817      rtarg1(i) = i * (-5.0)
1818      if (realne(rpte1(i), rtarg1(i))) then
1819         ! Error #206
1820         errors(206) = .true.
1821      endif
1822
1823      chpte1(i) = 'a'
1824      if (chne(chpte1(i), chtarg1(i))) then
1825         ! Error #207
1826         errors(207) = .true.
1827      endif
1828
1829      chtarg1(i) = 'z'
1830      if (chne(chpte1(i), chtarg1(i))) then
1831         ! Error #208
1832         errors(208) = .true.
1833      endif
1834
1835      ch8pte1(i) = 'aaaaaaaa'
1836      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1837         ! Error #209
1838         errors(209) = .true.
1839      endif
1840
1841      ch8targ1(i) = 'zzzzzzzz'
1842      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
1843         ! Error #210
1844         errors(210) = .true.
1845      endif
1846
1847      do, j=1,m
1848         dpte2(j,i)%r1=1.0
1849         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1850            ! Error #211
1851            errors(211) = .true.
1852         endif
1853
1854         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
1855         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
1856            ! Error #212
1857            errors(212) = .true.
1858         endif
1859
1860         ipte2(j,i) = i
1861         if (intne(ipte2(j,i), itarg2(j,i))) then
1862            ! Error #213
1863            errors(213) = .true.
1864         endif
1865
1866         itarg2(j,i) = -ipte2(j,i)
1867         if (intne(ipte2(j,i), itarg2(j,i))) then
1868            ! Error #214
1869            errors(214) = .true.
1870         endif
1871
1872         rpte2(j,i) = i * (-2.0)
1873         if (realne(rpte2(j,i), rtarg2(j,i))) then
1874            ! Error #215
1875            errors(215) = .true.
1876         endif
1877
1878         rtarg2(j,i) = i * (-3.0)
1879         if (realne(rpte2(j,i), rtarg2(j,i))) then
1880            ! Error #216
1881            errors(216) = .true.
1882         endif
1883
1884         chpte2(j,i) = 'a'
1885         if (chne(chpte2(j,i), chtarg2(j,i))) then
1886            ! Error #217
1887            errors(217) = .true.
1888         endif
1889
1890         chtarg2(j,i) = 'z'
1891         if (chne(chpte2(j,i), chtarg2(j,i))) then
1892            ! Error #218
1893            errors(218) = .true.
1894         endif
1895
1896         ch8pte2(j,i) = 'aaaaaaaa'
1897         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1898            ! Error #219
1899            errors(219) = .true.
1900         endif
1901
1902         ch8targ2(j,i) = 'zzzzzzzz'
1903         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
1904            ! Error #220
1905            errors(220) = .true.
1906         endif
1907         do k=1,o
1908            dpte3(k,j,i)%i2(1+mod(i,5))=i
1909            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1910                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1911               ! Error #221
1912               errors(221) = .true.
1913            endif
1914
1915            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
1916            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
1917                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
1918               ! Error #222
1919               errors(222) = .true.
1920            endif
1921
1922            ipte3(k,j,i) = i
1923            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1924               ! Error #223
1925               errors(223) = .true.
1926            endif
1927
1928            itarg3(k,j,i) = -ipte3(k,j,i)
1929            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
1930               ! Error #224
1931               errors(224) = .true.
1932            endif
1933
1934            rpte3(k,j,i) = i * 2.0
1935            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1936               ! Error #225
1937               errors(225) = .true.
1938            endif
1939
1940            rtarg3(k,j,i) = i * 3.0
1941            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
1942               ! Error #226
1943               errors(226) = .true.
1944            endif
1945
1946            chpte3(k,j,i) = 'a'
1947            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1948               ! Error #227
1949               errors(227) = .true.
1950            endif
1951
1952            chtarg3(k,j,i) = 'z'
1953            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
1954               ! Error #228
1955               errors(228) = .true.
1956            endif
1957
1958            ch8pte3(k,j,i) = 'aaaaaaaa'
1959            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1960               ! Error #229
1961               errors(229) = .true.
1962            endif
1963
1964            ch8targ3(k,j,i) = 'zzzzzzzz'
1965            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
1966               ! Error #230
1967               errors(230) = .true.
1968            endif
1969         end do
1970      end do
1971   end do
1972
1973 end subroutine ptr7
1974
1975 subroutine ptr8
1976   common /errors/errors(400)
1977   logical :: errors, intne, realne, chne, ch8ne
1978   integer :: i,j,k
1979   integer, parameter :: n = 9
1980   integer, parameter :: m = 10
1981   integer, parameter :: o = 11
1982   integer itarg1 (n)
1983   integer itarg2 (m,n)
1984   integer itarg3 (o,m,n)
1985   real rtarg1(n)
1986   real rtarg2(m,n)
1987   real rtarg3(o,m,n)
1988   character chtarg1(n)
1989   character chtarg2(m,n)
1990   character chtarg3(o,m,n)
1991   character*8 ch8targ1(n)
1992   character*8 ch8targ2(m,n)
1993   character*8 ch8targ3(o,m,n)
1994   type drvd
1995      real r1
1996      integer i1
1997      integer i2(5)
1998   end type drvd
1999   type(drvd) dtarg1(n)
2000   type(drvd) dtarg2(m,n)
2001   type(drvd) dtarg3(o,m,n)
2002
2003   pointer(iptr1,dpte1)
2004   pointer(iptr2,dpte2)
2005   pointer(iptr3,dpte3)
2006   pointer(iptr4,ipte1)
2007   pointer(iptr5,ipte2)
2008   pointer(iptr6,ipte3)
2009   pointer(iptr7,rpte1)
2010   pointer(iptr8,rpte2)
2011   pointer(iptr9,rpte3)
2012   pointer(iptr10,chpte1)
2013   pointer(iptr11,chpte2)
2014   pointer(iptr12,chpte3)
2015   pointer(iptr13,ch8pte1)
2016   pointer(iptr14,ch8pte2)
2017   pointer(iptr15,ch8pte3)
2018
2019   type(drvd) dpte1(*)
2020   type(drvd) dpte2(m,*)
2021   type(drvd) dpte3(o,m,*)
2022   integer ipte1 (*)
2023   integer ipte2 (m,*)
2024   integer ipte3 (o,m,*)
2025   real rpte1(*)
2026   real rpte2(m,*)
2027   real rpte3(o,m,*)
2028   character chpte1(*)
2029   character chpte2(m,*)
2030   character chpte3(o,m,*)
2031   character*8 ch8pte1(*)
2032   character*8 ch8pte2(m,*)
2033   character*8 ch8pte3(o,m,*)
2034
2035   iptr1 = loc(dtarg1)
2036   iptr2 = loc(dtarg2)
2037   iptr3 = loc(dtarg3)
2038   iptr4 = loc(itarg1)
2039   iptr5 = loc(itarg2)
2040   iptr6 = loc(itarg3)
2041   iptr7 = loc(rtarg1)
2042   iptr8 = loc(rtarg2)
2043   iptr9 = loc(rtarg3)
2044   iptr10= loc(chtarg1)
2045   iptr11= loc(chtarg2)
2046   iptr12= loc(chtarg3)
2047   iptr13= loc(ch8targ1)
2048   iptr14= loc(ch8targ2)
2049   iptr15= loc(ch8targ3)
2050
2051
2052   do, i=1,n
2053      dpte1(i)%i1=i
2054      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2055         ! Error #231
2056         errors(231) = .true.
2057      endif
2058
2059      dtarg1(i)%i1=2*dpte1(i)%i1
2060      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2061         ! Error #232
2062         errors(232) = .true.
2063      endif
2064
2065      ipte1(i) = i
2066      if (intne(ipte1(i), itarg1(i))) then
2067         ! Error #233
2068         errors(233) = .true.
2069      endif
2070
2071      itarg1(i) = -ipte1(i)
2072      if (intne(ipte1(i), itarg1(i))) then
2073         ! Error #234
2074         errors(234) = .true.
2075      endif
2076
2077      rpte1(i) = i * 5.0
2078      if (realne(rpte1(i), rtarg1(i))) then
2079         ! Error #235
2080         errors(235) = .true.
2081      endif
2082
2083      rtarg1(i) = i * (-5.0)
2084      if (realne(rpte1(i), rtarg1(i))) then
2085         ! Error #236
2086         errors(236) = .true.
2087      endif
2088
2089      chpte1(i) = 'a'
2090      if (chne(chpte1(i), chtarg1(i))) then
2091         ! Error #237
2092         errors(237) = .true.
2093      endif
2094
2095      chtarg1(i) = 'z'
2096      if (chne(chpte1(i), chtarg1(i))) then
2097         ! Error #238
2098         errors(238) = .true.
2099      endif
2100
2101      ch8pte1(i) = 'aaaaaaaa'
2102      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2103         ! Error #239
2104         errors(239) = .true.
2105      endif
2106
2107      ch8targ1(i) = 'zzzzzzzz'
2108      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2109         ! Error #240
2110         errors(240) = .true.
2111      endif
2112
2113      do, j=1,m
2114         dpte2(j,i)%r1=1.0
2115         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2116            ! Error #241
2117            errors(241) = .true.
2118         endif
2119
2120         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
2121         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2122            ! Error #242
2123            errors(242) = .true.
2124         endif
2125
2126         ipte2(j,i) = i
2127         if (intne(ipte2(j,i), itarg2(j,i))) then
2128            ! Error #243
2129            errors(243) = .true.
2130         endif
2131
2132         itarg2(j,i) = -ipte2(j,i)
2133         if (intne(ipte2(j,i), itarg2(j,i))) then
2134            ! Error #244
2135            errors(244) = .true.
2136         endif
2137
2138         rpte2(j,i) = i * (-2.0)
2139         if (realne(rpte2(j,i), rtarg2(j,i))) then
2140            ! Error #245
2141            errors(245) = .true.
2142         endif
2143
2144         rtarg2(j,i) = i * (-3.0)
2145         if (realne(rpte2(j,i), rtarg2(j,i))) then
2146            ! Error #246
2147            errors(246) = .true.
2148         endif
2149
2150         chpte2(j,i) = 'a'
2151         if (chne(chpte2(j,i), chtarg2(j,i))) then
2152            ! Error #247
2153            errors(247) = .true.
2154         endif
2155
2156         chtarg2(j,i) = 'z'
2157         if (chne(chpte2(j,i), chtarg2(j,i))) then
2158            ! Error #248
2159            errors(248) = .true.
2160         endif
2161
2162         ch8pte2(j,i) = 'aaaaaaaa'
2163         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2164            ! Error #249
2165            errors(249) = .true.
2166         endif
2167
2168         ch8targ2(j,i) = 'zzzzzzzz'
2169         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2170            ! Error #250
2171            errors(250) = .true.
2172         endif
2173         do k=1,o
2174            dpte3(k,j,i)%i2(1+mod(i,5))=i
2175            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2176                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2177               ! Error #251
2178               errors(251) = .true.
2179            endif
2180
2181            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
2182            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2183                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2184               ! Error #252
2185               errors(252) = .true.
2186            endif
2187
2188            ipte3(k,j,i) = i
2189            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2190               ! Error #253
2191               errors(253) = .true.
2192            endif
2193
2194            itarg3(k,j,i) = -ipte3(k,j,i)
2195            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2196               ! Error #254
2197               errors(254) = .true.
2198            endif
2199
2200            rpte3(k,j,i) = i * 2.0
2201            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2202               ! Error #255
2203               errors(255) = .true.
2204            endif
2205
2206            rtarg3(k,j,i) = i * 3.0
2207            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2208               ! Error #256
2209               errors(256) = .true.
2210            endif
2211
2212            chpte3(k,j,i) = 'a'
2213            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2214               ! Error #257
2215               errors(257) = .true.
2216            endif
2217
2218            chtarg3(k,j,i) = 'z'
2219            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2220               ! Error #258
2221               errors(258) = .true.
2222            endif
2223
2224            ch8pte3(k,j,i) = 'aaaaaaaa'
2225            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2226               ! Error #259
2227               errors(259) = .true.
2228            endif
2229
2230            ch8targ3(k,j,i) = 'zzzzzzzz'
2231            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2232               ! Error #260
2233               errors(260) = .true.
2234            endif
2235         end do
2236      end do
2237   end do
2238 end subroutine ptr8
2239
2240
2241 subroutine ptr9(nnn,mmm,ooo)
2242   common /errors/errors(400)
2243   logical :: errors, intne, realne, chne, ch8ne
2244   integer :: i,j,k
2245   integer :: nnn,mmm,ooo
2246   integer, parameter :: n = 9
2247   integer, parameter :: m = 10
2248   integer, parameter :: o = 11
2249   integer itarg1 (n)
2250   integer itarg2 (m,n)
2251   integer itarg3 (o,m,n)
2252   real rtarg1(n)
2253   real rtarg2(m,n)
2254   real rtarg3(o,m,n)
2255   character chtarg1(n)
2256   character chtarg2(m,n)
2257   character chtarg3(o,m,n)
2258   character*8 ch8targ1(n)
2259   character*8 ch8targ2(m,n)
2260   character*8 ch8targ3(o,m,n)
2261   type drvd
2262      real r1
2263      integer i1
2264      integer i2(5)
2265   end type drvd
2266   type(drvd) dtarg1(n)
2267   type(drvd) dtarg2(m,n)
2268   type(drvd) dtarg3(o,m,n)
2269
2270   type(drvd) dpte1(nnn)
2271   type(drvd) dpte2(mmm,nnn)
2272   type(drvd) dpte3(ooo,mmm,nnn)
2273   integer ipte1 (nnn)
2274   integer ipte2 (mmm,nnn)
2275   integer ipte3 (ooo,mmm,nnn)
2276   real rpte1(nnn)
2277   real rpte2(mmm,nnn)
2278   real rpte3(ooo,mmm,nnn)
2279   character chpte1(nnn)
2280   character chpte2(mmm,nnn)
2281   character chpte3(ooo,mmm,nnn)
2282   character*8 ch8pte1(nnn)
2283   character*8 ch8pte2(mmm,nnn)
2284   character*8 ch8pte3(ooo,mmm,nnn)
2285
2286   pointer(iptr1,dpte1)
2287   pointer(iptr2,dpte2)
2288   pointer(iptr3,dpte3)
2289   pointer(iptr4,ipte1)
2290   pointer(iptr5,ipte2)
2291   pointer(iptr6,ipte3)
2292   pointer(iptr7,rpte1)
2293   pointer(iptr8,rpte2)
2294   pointer(iptr9,rpte3)
2295   pointer(iptr10,chpte1)
2296   pointer(iptr11,chpte2)
2297   pointer(iptr12,chpte3)
2298   pointer(iptr13,ch8pte1)
2299   pointer(iptr14,ch8pte2)
2300   pointer(iptr15,ch8pte3)
2301
2302   iptr1 = loc(dtarg1)
2303   iptr2 = loc(dtarg2)
2304   iptr3 = loc(dtarg3)
2305   iptr4 = loc(itarg1)
2306   iptr5 = loc(itarg2)
2307   iptr6 = loc(itarg3)
2308   iptr7 = loc(rtarg1)
2309   iptr8 = loc(rtarg2)
2310   iptr9 = loc(rtarg3)
2311   iptr10= loc(chtarg1)
2312   iptr11= loc(chtarg2)
2313   iptr12= loc(chtarg3)
2314   iptr13= loc(ch8targ1)
2315   iptr14= loc(ch8targ2)
2316   iptr15= loc(ch8targ3)
2317
2318
2319   do, i=1,n
2320      dpte1(i)%i1=i
2321      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2322         ! Error #261
2323         errors(261) = .true.
2324      endif
2325
2326      dtarg1(i)%i1=2*dpte1(i)%i1
2327      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2328         ! Error #262
2329         errors(262) = .true.
2330      endif
2331
2332      ipte1(i) = i
2333      if (intne(ipte1(i), itarg1(i))) then
2334         ! Error #263
2335         errors(263) = .true.
2336      endif
2337
2338      itarg1(i) = -ipte1(i)
2339      if (intne(ipte1(i), itarg1(i))) then
2340         ! Error #264
2341         errors(264) = .true.
2342      endif
2343
2344      rpte1(i) = i * 5.0
2345      if (realne(rpte1(i), rtarg1(i))) then
2346         ! Error #265
2347         errors(265) = .true.
2348      endif
2349
2350      rtarg1(i) = i * (-5.0)
2351      if (realne(rpte1(i), rtarg1(i))) then
2352         ! Error #266
2353         errors(266) = .true.
2354      endif
2355
2356      chpte1(i) = 'a'
2357      if (chne(chpte1(i), chtarg1(i))) then
2358         ! Error #267
2359         errors(267) = .true.
2360      endif
2361
2362      chtarg1(i) = 'z'
2363      if (chne(chpte1(i), chtarg1(i))) then
2364         ! Error #268
2365         errors(268) = .true.
2366      endif
2367
2368      ch8pte1(i) = 'aaaaaaaa'
2369      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2370         ! Error #269
2371         errors(269) = .true.
2372      endif
2373
2374      ch8targ1(i) = 'zzzzzzzz'
2375      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2376         ! Error #270
2377         errors(270) = .true.
2378      endif
2379
2380      do, j=1,m
2381         dpte2(j,i)%r1=1.0
2382         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2383            ! Error #271
2384            errors(271) = .true.
2385         endif
2386
2387         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
2388         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2389            ! Error #272
2390            errors(272) = .true.
2391         endif
2392
2393         ipte2(j,i) = i
2394         if (intne(ipte2(j,i), itarg2(j,i))) then
2395            ! Error #273
2396            errors(273) = .true.
2397         endif
2398
2399         itarg2(j,i) = -ipte2(j,i)
2400         if (intne(ipte2(j,i), itarg2(j,i))) then
2401            ! Error #274
2402            errors(274) = .true.
2403         endif
2404
2405         rpte2(j,i) = i * (-2.0)
2406         if (realne(rpte2(j,i), rtarg2(j,i))) then
2407            ! Error #275
2408            errors(275) = .true.
2409         endif
2410
2411         rtarg2(j,i) = i * (-3.0)
2412         if (realne(rpte2(j,i), rtarg2(j,i))) then
2413            ! Error #276
2414            errors(276) = .true.
2415         endif
2416
2417         chpte2(j,i) = 'a'
2418         if (chne(chpte2(j,i), chtarg2(j,i))) then
2419            ! Error #277
2420            errors(277) = .true.
2421         endif
2422
2423         chtarg2(j,i) = 'z'
2424         if (chne(chpte2(j,i), chtarg2(j,i))) then
2425            ! Error #278
2426            errors(278) = .true.
2427         endif
2428
2429         ch8pte2(j,i) = 'aaaaaaaa'
2430         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2431            ! Error #279
2432            errors(279) = .true.
2433         endif
2434
2435         ch8targ2(j,i) = 'zzzzzzzz'
2436         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2437            ! Error #280
2438            errors(280) = .true.
2439         endif
2440         do k=1,o
2441            dpte3(k,j,i)%i2(1+mod(i,5))=i
2442            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2443                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2444               ! Error #281
2445               errors(281) = .true.
2446            endif
2447
2448            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
2449            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2450                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2451               ! Error #282
2452               errors(282) = .true.
2453            endif
2454
2455            ipte3(k,j,i) = i
2456            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2457               ! Error #283
2458               errors(283) = .true.
2459            endif
2460
2461            itarg3(k,j,i) = -ipte3(k,j,i)
2462            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2463               ! Error #284
2464               errors(284) = .true.
2465            endif
2466
2467            rpte3(k,j,i) = i * 2.0
2468            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2469               ! Error #285
2470               errors(285) = .true.
2471            endif
2472
2473            rtarg3(k,j,i) = i * 3.0
2474            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2475               ! Error #286
2476               errors(286) = .true.
2477            endif
2478
2479            chpte3(k,j,i) = 'a'
2480            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2481               ! Error #287
2482               errors(287) = .true.
2483            endif
2484
2485            chtarg3(k,j,i) = 'z'
2486            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2487               ! Error #288
2488               errors(288) = .true.
2489            endif
2490
2491            ch8pte3(k,j,i) = 'aaaaaaaa'
2492            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2493               ! Error #289
2494               errors(289) = .true.
2495            endif
2496
2497            ch8targ3(k,j,i) = 'zzzzzzzz'
2498            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2499               ! Error #290
2500               errors(290) = .true.
2501            endif
2502         end do
2503      end do
2504   end do
2505
2506   rtarg3 = .5
2507   ! Vector syntax
2508   do, i=1,n
2509      ipte3 = i
2510      rpte3 = rpte3+1
2511      do, j=1,m
2512         do k=1,o
2513            if (intne(itarg3(k,j,i), i)) then
2514               ! Error #291
2515               errors(291) = .true.
2516            endif
2517
2518            if (realne(rtarg3(k,j,i), i+.5)) then
2519               ! Error #292
2520               errors(292) = .true.
2521            endif
2522         end do
2523      end do
2524   end do
2525
2526 end subroutine ptr9
2527
2528 subroutine ptr10(nnn,mmm,ooo)
2529   common /errors/errors(400)
2530   logical :: errors, intne, realne, chne, ch8ne
2531   integer :: i,j,k
2532   integer :: nnn,mmm,ooo
2533   integer, parameter :: n = 9
2534   integer, parameter :: m = 10
2535   integer, parameter :: o = 11
2536   integer itarg1 (n)
2537   integer itarg2 (m,n)
2538   integer itarg3 (o,m,n)
2539   real rtarg1(n)
2540   real rtarg2(m,n)
2541   real rtarg3(o,m,n)
2542   character chtarg1(n)
2543   character chtarg2(m,n)
2544   character chtarg3(o,m,n)
2545   character*8 ch8targ1(n)
2546   character*8 ch8targ2(m,n)
2547   character*8 ch8targ3(o,m,n)
2548   type drvd
2549      real r1
2550      integer i1
2551      integer i2(5)
2552   end type drvd
2553   type(drvd) dtarg1(n)
2554   type(drvd) dtarg2(m,n)
2555   type(drvd) dtarg3(o,m,n)
2556
2557   type(drvd) dpte1
2558   type(drvd) dpte2
2559   type(drvd) dpte3
2560   integer ipte1
2561   integer ipte2
2562   integer ipte3
2563   real rpte1
2564   real rpte2
2565   real rpte3
2566   character chpte1
2567   character chpte2
2568   character chpte3
2569   character*8 ch8pte1
2570   character*8 ch8pte2
2571   character*8 ch8pte3
2572
2573   pointer(iptr1,dpte1(nnn))
2574   pointer(iptr2,dpte2(mmm,nnn))
2575   pointer(iptr3,dpte3(ooo,mmm,nnn))
2576   pointer(iptr4,ipte1(nnn))
2577   pointer(iptr5,ipte2 (mmm,nnn))
2578   pointer(iptr6,ipte3(ooo,mmm,nnn))
2579   pointer(iptr7,rpte1(nnn))
2580   pointer(iptr8,rpte2(mmm,nnn))
2581   pointer(iptr9,rpte3(ooo,mmm,nnn))
2582   pointer(iptr10,chpte1(nnn))
2583   pointer(iptr11,chpte2(mmm,nnn))
2584   pointer(iptr12,chpte3(ooo,mmm,nnn))
2585   pointer(iptr13,ch8pte1(nnn))
2586   pointer(iptr14,ch8pte2(mmm,nnn))
2587   pointer(iptr15,ch8pte3(ooo,mmm,nnn))
2588
2589   iptr1 = loc(dtarg1)
2590   iptr2 = loc(dtarg2)
2591   iptr3 = loc(dtarg3)
2592   iptr4 = loc(itarg1)
2593   iptr5 = loc(itarg2)
2594   iptr6 = loc(itarg3)
2595   iptr7 = loc(rtarg1)
2596   iptr8 = loc(rtarg2)
2597   iptr9 = loc(rtarg3)
2598   iptr10= loc(chtarg1)
2599   iptr11= loc(chtarg2)
2600   iptr12= loc(chtarg3)
2601   iptr13= loc(ch8targ1)
2602   iptr14= loc(ch8targ2)
2603   iptr15= loc(ch8targ3)
2604
2605   do, i=1,n
2606      dpte1(i)%i1=i
2607      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2608         ! Error #293
2609         errors(293) = .true.
2610      endif
2611
2612      dtarg1(i)%i1=2*dpte1(i)%i1
2613      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2614         ! Error #294
2615         errors(294) = .true.
2616      endif
2617
2618      ipte1(i) = i
2619      if (intne(ipte1(i), itarg1(i))) then
2620         ! Error #295
2621         errors(295) = .true.
2622      endif
2623
2624      itarg1(i) = -ipte1(i)
2625      if (intne(ipte1(i), itarg1(i))) then
2626         ! Error #296
2627         errors(296) = .true.
2628      endif
2629
2630      rpte1(i) = i * 5.0
2631      if (realne(rpte1(i), rtarg1(i))) then
2632         ! Error #297
2633         errors(297) = .true.
2634      endif
2635
2636      rtarg1(i) = i * (-5.0)
2637      if (realne(rpte1(i), rtarg1(i))) then
2638         ! Error #298
2639         errors(298) = .true.
2640      endif
2641
2642      chpte1(i) = 'a'
2643      if (chne(chpte1(i), chtarg1(i))) then
2644         ! Error #299
2645         errors(299) = .true.
2646      endif
2647
2648      chtarg1(i) = 'z'
2649      if (chne(chpte1(i), chtarg1(i))) then
2650         ! Error #300
2651         errors(300) = .true.
2652      endif
2653
2654      ch8pte1(i) = 'aaaaaaaa'
2655      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2656         ! Error #301
2657         errors(301) = .true.
2658      endif
2659
2660      ch8targ1(i) = 'zzzzzzzz'
2661      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2662         ! Error #302
2663         errors(302) = .true.
2664      endif
2665
2666      do, j=1,m
2667         dpte2(j,i)%r1=1.0
2668         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2669            ! Error #303
2670            errors(303) = .true.
2671         endif
2672
2673         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
2674         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2675            ! Error #304
2676            errors(304) = .true.
2677         endif
2678
2679         ipte2(j,i) = i
2680         if (intne(ipte2(j,i), itarg2(j,i))) then
2681            ! Error #305
2682            errors(305) = .true.
2683         endif
2684
2685         itarg2(j,i) = -ipte2(j,i)
2686         if (intne(ipte2(j,i), itarg2(j,i))) then
2687            ! Error #306
2688            errors(306) = .true.
2689         endif
2690
2691         rpte2(j,i) = i * (-2.0)
2692         if (realne(rpte2(j,i), rtarg2(j,i))) then
2693            ! Error #307
2694            errors(307) = .true.
2695         endif
2696
2697         rtarg2(j,i) = i * (-3.0)
2698         if (realne(rpte2(j,i), rtarg2(j,i))) then
2699            ! Error #308
2700            errors(308) = .true.
2701         endif
2702
2703         chpte2(j,i) = 'a'
2704         if (chne(chpte2(j,i), chtarg2(j,i))) then
2705            ! Error #309
2706            errors(309) = .true.
2707         endif
2708
2709         chtarg2(j,i) = 'z'
2710         if (chne(chpte2(j,i), chtarg2(j,i))) then
2711            ! Error #310
2712            errors(310) = .true.
2713         endif
2714
2715         ch8pte2(j,i) = 'aaaaaaaa'
2716         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2717            ! Error #311
2718            errors(311) = .true.
2719         endif
2720
2721         ch8targ2(j,i) = 'zzzzzzzz'
2722         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
2723            ! Error #312
2724            errors(312) = .true.
2725         endif
2726         do k=1,o
2727            dpte3(k,j,i)%i2(1+mod(i,5))=i
2728            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2729                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2730               ! Error #313
2731               errors(313) = .true.
2732            endif
2733
2734            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
2735            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
2736                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
2737               ! Error #314
2738               errors(314) = .true.
2739            endif
2740
2741            ipte3(k,j,i) = i
2742            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2743               ! Error #315
2744               errors(315) = .true.
2745            endif
2746
2747            itarg3(k,j,i) = -ipte3(k,j,i)
2748            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
2749               ! Error #316
2750               errors(316) = .true.
2751            endif
2752
2753            rpte3(k,j,i) = i * 2.0
2754            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2755               ! Error #317
2756               errors(317) = .true.
2757            endif
2758
2759            rtarg3(k,j,i) = i * 3.0
2760            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
2761               ! Error #318
2762               errors(318) = .true.
2763            endif
2764
2765            chpte3(k,j,i) = 'a'
2766            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2767               ! Error #319
2768               errors(319) = .true.
2769            endif
2770
2771            chtarg3(k,j,i) = 'z'
2772            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
2773               ! Error #320
2774               errors(320) = .true.
2775            endif
2776
2777            ch8pte3(k,j,i) = 'aaaaaaaa'
2778            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2779               ! Error #321
2780               errors(321) = .true.
2781            endif
2782
2783            ch8targ3(k,j,i) = 'zzzzzzzz'
2784            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
2785               ! Error #322
2786               errors(322) = .true.
2787            endif
2788         end do
2789      end do
2790   end do
2791
2792   rtarg3 = .5
2793   ! Vector syntax
2794   do, i=1,n
2795      ipte3 = i
2796      rpte3 = rpte3+1
2797      do, j=1,m
2798         do k=1,o
2799            if (intne(itarg3(k,j,i), i)) then
2800               ! Error #323
2801               errors(323) = .true.
2802            endif
2803
2804            if (realne(rtarg3(k,j,i), i+.5)) then
2805               ! Error #324
2806               errors(324) = .true.
2807            endif
2808         end do
2809      end do
2810   end do
2811 end subroutine ptr10
2812
2813 subroutine ptr11(nnn,mmm,ooo)
2814   common /errors/errors(400)
2815   logical :: errors, intne, realne, chne, ch8ne
2816   integer :: i,j,k
2817   integer :: nnn,mmm,ooo
2818   integer, parameter :: n = 9
2819   integer, parameter :: m = 10
2820   integer, parameter :: o = 11
2821   integer itarg1 (n)
2822   integer itarg2 (m,n)
2823   integer itarg3 (o,m,n)
2824   real rtarg1(n)
2825   real rtarg2(m,n)
2826   real rtarg3(o,m,n)
2827   character chtarg1(n)
2828   character chtarg2(m,n)
2829   character chtarg3(o,m,n)
2830   character*8 ch8targ1(n)
2831   character*8 ch8targ2(m,n)
2832   character*8 ch8targ3(o,m,n)
2833   type drvd
2834      real r1
2835      integer i1
2836      integer i2(5)
2837   end type drvd
2838   type(drvd) dtarg1(n)
2839   type(drvd) dtarg2(m,n)
2840   type(drvd) dtarg3(o,m,n)
2841
2842   pointer(iptr1,dpte1(nnn))
2843   pointer(iptr2,dpte2(mmm,nnn))
2844   pointer(iptr3,dpte3(ooo,mmm,nnn))
2845   pointer(iptr4,ipte1(nnn))
2846   pointer(iptr5,ipte2 (mmm,nnn))
2847   pointer(iptr6,ipte3(ooo,mmm,nnn))
2848   pointer(iptr7,rpte1(nnn))
2849   pointer(iptr8,rpte2(mmm,nnn))
2850   pointer(iptr9,rpte3(ooo,mmm,nnn))
2851   pointer(iptr10,chpte1(nnn))
2852   pointer(iptr11,chpte2(mmm,nnn))
2853   pointer(iptr12,chpte3(ooo,mmm,nnn))
2854   pointer(iptr13,ch8pte1(nnn))
2855   pointer(iptr14,ch8pte2(mmm,nnn))
2856   pointer(iptr15,ch8pte3(ooo,mmm,nnn))
2857
2858   type(drvd) dpte1
2859   type(drvd) dpte2
2860   type(drvd) dpte3
2861   integer ipte1
2862   integer ipte2
2863   integer ipte3
2864   real rpte1
2865   real rpte2
2866   real rpte3
2867   character chpte1
2868   character chpte2
2869   character chpte3
2870   character*8 ch8pte1
2871   character*8 ch8pte2
2872   character*8 ch8pte3
2873
2874   iptr1 = loc(dtarg1)
2875   iptr2 = loc(dtarg2)
2876   iptr3 = loc(dtarg3)
2877   iptr4 = loc(itarg1)
2878   iptr5 = loc(itarg2)
2879   iptr6 = loc(itarg3)
2880   iptr7 = loc(rtarg1)
2881   iptr8 = loc(rtarg2)
2882   iptr9 = loc(rtarg3)
2883   iptr10= loc(chtarg1)
2884   iptr11= loc(chtarg2)
2885   iptr12= loc(chtarg3)
2886   iptr13= loc(ch8targ1)
2887   iptr14= loc(ch8targ2)
2888   iptr15= loc(ch8targ3)
2889
2890   do, i=1,n
2891      dpte1(i)%i1=i
2892      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2893         ! Error #325
2894         errors(325) = .true.
2895      endif
2896
2897      dtarg1(i)%i1=2*dpte1(i)%i1
2898      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
2899         ! Error #326
2900         errors(326) = .true.
2901      endif
2902
2903      ipte1(i) = i
2904      if (intne(ipte1(i), itarg1(i))) then
2905         ! Error #327
2906         errors(327) = .true.
2907      endif
2908
2909      itarg1(i) = -ipte1(i)
2910      if (intne(ipte1(i), itarg1(i))) then
2911         ! Error #328
2912         errors(328) = .true.
2913      endif
2914
2915      rpte1(i) = i * 5.0
2916      if (realne(rpte1(i), rtarg1(i))) then
2917         ! Error #329
2918         errors(329) = .true.
2919      endif
2920
2921      rtarg1(i) = i * (-5.0)
2922      if (realne(rpte1(i), rtarg1(i))) then
2923         ! Error #330
2924         errors(330) = .true.
2925      endif
2926
2927      chpte1(i) = 'a'
2928      if (chne(chpte1(i), chtarg1(i))) then
2929         ! Error #331
2930         errors(331) = .true.
2931      endif
2932
2933      chtarg1(i) = 'z'
2934      if (chne(chpte1(i), chtarg1(i))) then
2935         ! Error #332
2936         errors(332) = .true.
2937      endif
2938
2939      ch8pte1(i) = 'aaaaaaaa'
2940      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2941         ! Error #333
2942         errors(333) = .true.
2943      endif
2944
2945      ch8targ1(i) = 'zzzzzzzz'
2946      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
2947         ! Error #334
2948         errors(334) = .true.
2949      endif
2950
2951      do, j=1,m
2952         dpte2(j,i)%r1=1.0
2953         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2954            ! Error #335
2955            errors(335) = .true.
2956         endif
2957
2958         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
2959         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
2960            ! Error #336
2961            errors(336) = .true.
2962         endif
2963
2964         ipte2(j,i) = i
2965         if (intne(ipte2(j,i), itarg2(j,i))) then
2966            ! Error #337
2967            errors(337) = .true.
2968         endif
2969
2970         itarg2(j,i) = -ipte2(j,i)
2971         if (intne(ipte2(j,i), itarg2(j,i))) then
2972            ! Error #338
2973            errors(338) = .true.
2974         endif
2975
2976         rpte2(j,i) = i * (-2.0)
2977         if (realne(rpte2(j,i), rtarg2(j,i))) then
2978            ! Error #339
2979            errors(339) = .true.
2980         endif
2981
2982         rtarg2(j,i) = i * (-3.0)
2983         if (realne(rpte2(j,i), rtarg2(j,i))) then
2984            ! Error #340
2985            errors(340) = .true.
2986         endif
2987
2988         chpte2(j,i) = 'a'
2989         if (chne(chpte2(j,i), chtarg2(j,i))) then
2990            ! Error #341
2991            errors(341) = .true.
2992         endif
2993
2994         chtarg2(j,i) = 'z'
2995         if (chne(chpte2(j,i), chtarg2(j,i))) then
2996            ! Error #342
2997            errors(342) = .true.
2998         endif
2999
3000         ch8pte2(j,i) = 'aaaaaaaa'
3001         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
3002            ! Error #343
3003            errors(343) = .true.
3004         endif
3005
3006         ch8targ2(j,i) = 'zzzzzzzz'
3007         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
3008            ! Error #344
3009            errors(344) = .true.
3010         endif
3011         do k=1,o
3012            dpte3(k,j,i)%i2(1+mod(i,5))=i
3013            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
3014                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
3015               ! Error #345
3016               errors(345) = .true.
3017            endif
3018
3019            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
3020            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
3021                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
3022               ! Error #346
3023               errors(346) = .true.
3024            endif
3025
3026            ipte3(k,j,i) = i
3027            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
3028               ! Error #347
3029               errors(347) = .true.
3030            endif
3031
3032            itarg3(k,j,i) = -ipte3(k,j,i)
3033            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
3034               ! Error #348
3035               errors(348) = .true.
3036            endif
3037
3038            rpte3(k,j,i) = i * 2.0
3039            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
3040               ! Error #349
3041               errors(349) = .true.
3042            endif
3043
3044            rtarg3(k,j,i) = i * 3.0
3045            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
3046               ! Error #350
3047               errors(350) = .true.
3048            endif
3049
3050            chpte3(k,j,i) = 'a'
3051            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
3052               ! Error #351
3053               errors(351) = .true.
3054            endif
3055
3056            chtarg3(k,j,i) = 'z'
3057            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
3058               ! Error #352
3059               errors(352) = .true.
3060            endif
3061
3062            ch8pte3(k,j,i) = 'aaaaaaaa'
3063            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
3064               ! Error #353
3065               errors(353) = .true.
3066            endif
3067
3068            ch8targ3(k,j,i) = 'zzzzzzzz'
3069            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
3070               ! Error #354
3071               errors(354) = .true.
3072            endif
3073         end do
3074      end do
3075   end do
3076
3077   rtarg3 = .5
3078   ! Vector syntax
3079   do, i=1,n
3080      ipte3 = i
3081      rpte3 = rpte3+1
3082      do, j=1,m
3083         do k=1,o
3084            if (intne(itarg3(k,j,i), i)) then
3085               ! Error #355
3086               errors(355) = .true.
3087            endif
3088
3089            if (realne(rtarg3(k,j,i), i+.5)) then
3090               ! Error #356
3091               errors(356) = .true.
3092            endif
3093         end do
3094      end do
3095   end do
3096 end subroutine ptr11
3097
3098 subroutine ptr12(nnn,mmm,ooo)
3099   common /errors/errors(400)
3100   logical :: errors, intne, realne, chne, ch8ne
3101   integer :: i,j,k
3102   integer :: nnn,mmm,ooo
3103   integer, parameter :: n = 9
3104   integer, parameter :: m = 10
3105   integer, parameter :: o = 11
3106   integer itarg1 (n)
3107   integer itarg2 (m,n)
3108   integer itarg3 (o,m,n)
3109   real rtarg1(n)
3110   real rtarg2(m,n)
3111   real rtarg3(o,m,n)
3112   character chtarg1(n)
3113   character chtarg2(m,n)
3114   character chtarg3(o,m,n)
3115   character*8 ch8targ1(n)
3116   character*8 ch8targ2(m,n)
3117   character*8 ch8targ3(o,m,n)
3118   type drvd
3119      real r1
3120      integer i1
3121      integer i2(5)
3122   end type drvd
3123   type(drvd) dtarg1(n)
3124   type(drvd) dtarg2(m,n)
3125   type(drvd) dtarg3(o,m,n)
3126
3127   pointer(iptr1,dpte1)
3128   pointer(iptr2,dpte2)
3129   pointer(iptr3,dpte3)
3130   pointer(iptr4,ipte1)
3131   pointer(iptr5,ipte2)
3132   pointer(iptr6,ipte3)
3133   pointer(iptr7,rpte1)
3134   pointer(iptr8,rpte2)
3135   pointer(iptr9,rpte3)
3136   pointer(iptr10,chpte1)
3137   pointer(iptr11,chpte2)
3138   pointer(iptr12,chpte3)
3139   pointer(iptr13,ch8pte1)
3140   pointer(iptr14,ch8pte2)
3141   pointer(iptr15,ch8pte3)
3142
3143   type(drvd) dpte1(nnn)
3144   type(drvd) dpte2(mmm,nnn)
3145   type(drvd) dpte3(ooo,mmm,nnn)
3146   integer ipte1 (nnn)
3147   integer ipte2 (mmm,nnn)
3148   integer ipte3 (ooo,mmm,nnn)
3149   real rpte1(nnn)
3150   real rpte2(mmm,nnn)
3151   real rpte3(ooo,mmm,nnn)
3152   character chpte1(nnn)
3153   character chpte2(mmm,nnn)
3154   character chpte3(ooo,mmm,nnn)
3155   character*8 ch8pte1(nnn)
3156   character*8 ch8pte2(mmm,nnn)
3157   character*8 ch8pte3(ooo,mmm,nnn)
3158
3159   iptr1 = loc(dtarg1)
3160   iptr2 = loc(dtarg2)
3161   iptr3 = loc(dtarg3)
3162   iptr4 = loc(itarg1)
3163   iptr5 = loc(itarg2)
3164   iptr6 = loc(itarg3)
3165   iptr7 = loc(rtarg1)
3166   iptr8 = loc(rtarg2)
3167   iptr9 = loc(rtarg3)
3168   iptr10= loc(chtarg1)
3169   iptr11= loc(chtarg2)
3170   iptr12= loc(chtarg3)
3171   iptr13= loc(ch8targ1)
3172   iptr14= loc(ch8targ2)
3173   iptr15= loc(ch8targ3)
3174
3175
3176   do, i=1,n
3177      dpte1(i)%i1=i
3178      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
3179         ! Error #357
3180         errors(357) = .true.
3181      endif
3182
3183      dtarg1(i)%i1=2*dpte1(i)%i1
3184      if (intne(dpte1(i)%i1, dtarg1(i)%i1)) then
3185         ! Error #358
3186         errors(358) = .true.
3187      endif
3188
3189      ipte1(i) = i
3190      if (intne(ipte1(i), itarg1(i))) then
3191         ! Error #359
3192         errors(359) = .true.
3193      endif
3194
3195      itarg1(i) = -ipte1(i)
3196      if (intne(ipte1(i), itarg1(i))) then
3197         ! Error #360
3198         errors(360) = .true.
3199      endif
3200
3201      rpte1(i) = i * 5.0
3202      if (realne(rpte1(i), rtarg1(i))) then
3203         ! Error #361
3204         errors(361) = .true.
3205      endif
3206
3207      rtarg1(i) = i * (-5.0)
3208      if (realne(rpte1(i), rtarg1(i))) then
3209         ! Error #362
3210         errors(362) = .true.
3211      endif
3212
3213      chpte1(i) = 'a'
3214      if (chne(chpte1(i), chtarg1(i))) then
3215         ! Error #363
3216         errors(363) = .true.
3217      endif
3218
3219      chtarg1(i) = 'z'
3220      if (chne(chpte1(i), chtarg1(i))) then
3221         ! Error #364
3222         errors(364) = .true.
3223      endif
3224
3225      ch8pte1(i) = 'aaaaaaaa'
3226      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
3227         ! Error #365
3228         errors(365) = .true.
3229      endif
3230
3231      ch8targ1(i) = 'zzzzzzzz'
3232      if (ch8ne(ch8pte1(i), ch8targ1(i))) then
3233         ! Error #366
3234         errors(366) = .true.
3235      endif
3236
3237      do, j=1,m
3238         dpte2(j,i)%r1=1.0
3239         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
3240            ! Error #367
3241            errors(367) = .true.
3242         endif
3243
3244         dtarg2(j,i)%r1=2*dpte2(j,i)%r1
3245         if (realne(dpte2(j,i)%r1, dtarg2(j,i)%r1)) then
3246            ! Error #368
3247            errors(368) = .true.
3248         endif
3249
3250         ipte2(j,i) = i
3251         if (intne(ipte2(j,i), itarg2(j,i))) then
3252            ! Error #369
3253            errors(369) = .true.
3254         endif
3255
3256         itarg2(j,i) = -ipte2(j,i)
3257         if (intne(ipte2(j,i), itarg2(j,i))) then
3258            ! Error #370
3259            errors(370) = .true.
3260         endif
3261
3262         rpte2(j,i) = i * (-2.0)
3263         if (realne(rpte2(j,i), rtarg2(j,i))) then
3264            ! Error #371
3265            errors(371) = .true.
3266         endif
3267
3268         rtarg2(j,i) = i * (-3.0)
3269         if (realne(rpte2(j,i), rtarg2(j,i))) then
3270            ! Error #372
3271            errors(372) = .true.
3272         endif
3273
3274         chpte2(j,i) = 'a'
3275         if (chne(chpte2(j,i), chtarg2(j,i))) then
3276            ! Error #373
3277            errors(373) = .true.
3278         endif
3279
3280         chtarg2(j,i) = 'z'
3281         if (chne(chpte2(j,i), chtarg2(j,i))) then
3282            ! Error #374
3283            errors(374) = .true.
3284         endif
3285
3286         ch8pte2(j,i) = 'aaaaaaaa'
3287         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
3288            ! Error #375
3289            errors(375) = .true.
3290         endif
3291
3292         ch8targ2(j,i) = 'zzzzzzzz'
3293         if (ch8ne(ch8pte2(j,i), ch8targ2(j,i))) then
3294            ! Error #376
3295            errors(376) = .true.
3296         endif
3297         do k=1,o
3298            dpte3(k,j,i)%i2(1+mod(i,5))=i
3299            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
3300                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
3301               ! Error #377
3302               errors(377) = .true.
3303            endif
3304
3305            dtarg3(k,j,i)%i2(1+mod(i,5))=2*dpte3(k,j,i)%i2(1+mod(i,5))
3306            if (intne(dpte3(k,j,i)%i2(1+mod(i,5)), &
3307                 dtarg3(k,j,i)%i2(1+mod(i,5)))) then
3308               ! Error #378
3309               errors(378) = .true.
3310            endif
3311
3312            ipte3(k,j,i) = i
3313            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
3314               ! Error #379
3315               errors(379) = .true.
3316            endif
3317
3318            itarg3(k,j,i) = -ipte3(k,j,i)
3319            if (intne(ipte3(k,j,i), itarg3(k,j,i))) then
3320               ! Error #380
3321               errors(380) = .true.
3322            endif
3323
3324            rpte3(k,j,i) = i * 2.0
3325            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
3326               ! Error #381
3327               errors(381) = .true.
3328            endif
3329
3330            rtarg3(k,j,i) = i * 3.0
3331            if (realne(rpte3(k,j,i), rtarg3(k,j,i))) then
3332               ! Error #382
3333               errors(382) = .true.
3334            endif
3335
3336            chpte3(k,j,i) = 'a'
3337            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
3338               ! Error #383
3339               errors(383) = .true.
3340            endif
3341
3342            chtarg3(k,j,i) = 'z'
3343            if (chne(chpte3(k,j,i), chtarg3(k,j,i))) then
3344               ! Error #384
3345               errors(384) = .true.
3346            endif
3347
3348            ch8pte3(k,j,i) = 'aaaaaaaa'
3349            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
3350               ! Error #385
3351               errors(385) = .true.
3352            endif
3353
3354            ch8targ3(k,j,i) = 'zzzzzzzz'
3355            if (ch8ne(ch8pte3(k,j,i), ch8targ3(k,j,i))) then
3356               ! Error #386
3357               errors(386) = .true.
3358            endif
3359         end do
3360      end do
3361   end do
3362
3363   rtarg3 = .5
3364   ! Vector syntax
3365   do, i=1,n
3366      ipte3 = i
3367      rpte3 = rpte3+1
3368      do, j=1,m
3369         do k=1,o
3370            if (intne(itarg3(k,j,i), i)) then
3371               ! Error #387
3372               errors(387) = .true.
3373            endif
3374
3375            if (realne(rtarg3(k,j,i), i+.5)) then
3376               ! Error #388
3377               errors(388) = .true.
3378            endif
3379         end do
3380      end do
3381   end do
3382
3383 end subroutine ptr12
3384
3385 ! Misc
3386 subroutine ptr13(nnn,mmm)
3387   common /errors/errors(400)
3388   logical :: errors, intne, realne, chne, ch8ne
3389   integer :: nnn,mmm
3390   integer :: i,j
3391   integer, parameter :: n = 9
3392   integer, parameter :: m = 10
3393   integer itarg1 (n)
3394   integer itarg2 (m,n)
3395   real rtarg1(n)
3396   real rtarg2(m,n)
3397
3398   integer ipte1
3399   integer ipte2
3400   real rpte1
3401   real rpte2
3402
3403   dimension ipte1(n)
3404   dimension rpte2(mmm,nnn)
3405
3406   pointer(iptr4,ipte1)
3407   pointer(iptr5,ipte2)
3408   pointer(iptr7,rpte1)
3409   pointer(iptr8,rpte2)
3410
3411   dimension ipte2(mmm,nnn)
3412   dimension rpte1(n)
3413
3414   iptr4 = loc(itarg1)
3415   iptr5 = loc(itarg2)
3416   iptr7 = loc(rtarg1)
3417   iptr8 = loc(rtarg2)  
3418
3419   do, i=1,n
3420      ipte1(i) = i
3421      if (intne(ipte1(i), itarg1(i))) then
3422         ! Error #389
3423         errors(389) = .true.
3424      endif
3425
3426      itarg1(i) = -ipte1(i)
3427      if (intne(ipte1(i), itarg1(i))) then
3428         ! Error #390
3429         errors(390) = .true.
3430      endif
3431
3432      rpte1(i) = i * 5.0
3433      if (realne(rpte1(i), rtarg1(i))) then
3434         ! Error #391
3435         errors(391) = .true.
3436      endif
3437
3438      rtarg1(i) = i * (-5.0)
3439      if (realne(rpte1(i), rtarg1(i))) then
3440         ! Error #392
3441         errors(392) = .true.
3442      endif
3443
3444      do, j=1,m
3445         ipte2(j,i) = i
3446         if (intne(ipte2(j,i), itarg2(j,i))) then
3447            ! Error #393
3448            errors(393) = .true.
3449         endif
3450
3451         itarg2(j,i) = -ipte2(j,i)
3452         if (intne(ipte2(j,i), itarg2(j,i))) then
3453            ! Error #394
3454            errors(394) = .true.
3455         endif
3456
3457         rpte2(j,i) = i * (-2.0)
3458         if (realne(rpte2(j,i), rtarg2(j,i))) then
3459            ! Error #395
3460            errors(395) = .true.
3461         endif
3462
3463         rtarg2(j,i) = i * (-3.0)
3464         if (realne(rpte2(j,i), rtarg2(j,i))) then
3465            ! Error #396
3466            errors(396) = .true.
3467         endif
3468
3469      end do
3470   end do
3471 end subroutine ptr13
3472
3473
3474 ! Test the passing of pointers and pointees as parameters
3475 subroutine parmtest
3476   integer, parameter :: n = 12
3477   integer, parameter :: m = 13
3478   integer iarray(m,n)
3479   pointer (ipt,iptee)
3480   integer iptee (m,n)
3481
3482   ipt = loc(iarray)
3483   !  write(*,*) "loc(iarray)",loc(iarray)
3484   call parmptr(ipt,iarray,n,m)
3485   !  write(*,*) "loc(iptee)",loc(iptee)
3486   call parmpte(iptee,iarray,n,m)
3487 end subroutine parmtest
3488
3489 subroutine parmptr(ipointer,intarr,n,m)
3490   common /errors/errors(400)
3491   logical :: errors, intne
3492   integer :: n,m,i,j
3493   integer intarr(m,n)
3494   pointer (ipointer,newpte)
3495   integer newpte(m,n)
3496   ! write(*,*) "loc(newpte)",loc(newpte)
3497   ! write(*,*) "loc(intarr)",loc(intarr) 
3498   ! write(*,*) "loc(newpte(1,1))",loc(newpte(1,1))
3499   ! newpte(1,1) = 101
3500   ! write(*,*) "newpte(1,1)=",newpte(1,1)
3501   ! write(*,*) "intarr(1,1)=",intarr(1,1)
3502   do, i=1,n
3503      do, j=1,m
3504         newpte(j,i) = i
3505         if (intne(newpte(j,i),intarr(j,i))) then
3506            ! Error #397
3507            errors(397) = .true.
3508         endif
3509
3510         call donothing(newpte(j,i),intarr(j,i))
3511         intarr(j,i) = -newpte(j,i)
3512         if (intne(newpte(j,i),intarr(j,i))) then
3513            ! Error #398
3514            errors(398) = .true.
3515         endif
3516      end do
3517   end do
3518 end subroutine parmptr
3519
3520 subroutine parmpte(pointee,intarr,n,m)
3521   common /errors/errors(400)
3522   logical :: errors, intne
3523   integer :: n,m,i,j
3524   integer pointee (m,n)
3525   integer intarr (m,n)
3526   !  write(*,*) "loc(pointee)",loc(pointee)
3527   !  write(*,*) "loc(intarr)",loc(intarr)
3528   !  write(*,*) "loc(pointee(1,1))",loc(pointee(1,1))
3529   !  pointee(1,1) = 99
3530   !  write(*,*) "pointee(1,1)=",pointee(1,1)
3531   !  write(*,*) "intarr(1,1)=",intarr(1,1)
3532
3533   do, i=1,n
3534      do, j=1,m
3535         pointee(j,i) = i
3536         if (intne(pointee(j,i),intarr(j,i))) then
3537            ! Error #399
3538            errors(399) = .true.
3539         endif
3540
3541         intarr(j,i) = 2*pointee(j,i)
3542         call donothing(pointee(j,i),intarr(j,i))
3543         if (intne(pointee(j,i),intarr(j,i))) then
3544            ! Error #400
3545            errors(400) = .true.
3546         endif
3547      end do
3548   end do
3549 end subroutine parmpte
3550
3551 ! Separate function calls to break Cray pointer-indifferent optimization
3552 logical function intne(ii,jj)
3553   integer :: i,j
3554   common /foo/foo
3555   integer foo
3556   foo = foo + 1
3557   intne = ii.ne.jj
3558   if (intne) then
3559      write (*,*) ii," doesn't equal ",jj
3560   endif
3561 end function intne
3562
3563 logical function realne(r1,r2)
3564   real :: r1, r2  
3565   common /foo/foo
3566   integer foo
3567   foo = foo + 1
3568   realne = r1.ne.r2
3569   if (realne) then
3570      write (*,*) r1," doesn't equal ",r2
3571   endif
3572 end function realne
3573
3574 logical function chne(ch1,ch2)
3575   character :: ch1, ch2  
3576   common /foo/foo
3577   integer foo
3578   foo = foo + 1
3579   chne = ch1.ne.ch2
3580   if (chne) then
3581      write (*,*) ch1," doesn't equal ",ch2
3582   endif
3583 end function chne
3584
3585 logical function ch8ne(ch1,ch2)
3586   character*8 :: ch1, ch2  
3587   common /foo/foo
3588   integer foo
3589   foo = foo + 1
3590   ch8ne = ch1.ne.ch2
3591   if (ch8ne) then
3592      write (*,*) ch1," doesn't equal ",ch2
3593   endif
3594 end function ch8ne
3595
3596 subroutine donothing(ii,jj)
3597   common/foo/foo
3598   integer :: ii,jj,foo
3599   if (foo.le.1) then
3600      foo = 1
3601   else
3602      foo = foo - 1
3603   endif
3604   if (foo.eq.0) then
3605      ii = -1
3606      jj = 1
3607 !     print *,"Test did not run correctly"
3608      call abort()
3609   endif
3610 end subroutine donothing
3611