1	program read_cgns_motion
2	USE CGNS
3
4! This program reads the CGNS file created with write_cgns_motion
5
6#ifdef WINNT
7	include 'cgnswin_f.h'
8#endif
9
10	parameter (Ndim = 3)
11	parameter (Nglobal = 500)
12	integer IndexDim, CellDim, PhysDim
13	integer ier, zonetype
14	integer nbases, nzones
15	integer(cgsize_t) size(Ndim*3)
16	integer nsols, location
17        integer datatype
18	character*32 basename, zonename
19	integer cg, base, zone, sol
20	character*32 name, filename
21	integer nndim, rind(6), num
22	integer(cgsize_t) dim_vals(12)
23	real*4 data_single(100000), version
24	double precision data_double(100000)
25	integer*4 data_int(100000)
26	character data_char(100000)
27
28! Variable for GridMotion_t:
29	integer nrmotion, rmotion, rmotiontype
30	character*32 rmotionname, arrayname
31	integer narrays
32	integer mass, length, time, temp, deg
33	integer ndescr, descr
34	character*32 descrname, descrtext
35	integer namotion, amotion, amotiontype
36	character*32 amotionname
37
38! Multiple GridCoordinates_t
39	integer grid, ngrids
40	character*32 gridname
41
42! *** Base/Zone IterativeData_t nodes
43        integer nsteps, step, mzone, start, end
44        character*32 bitername, zitername
45
46! Iterative/Time accurate Data
47	integer simulation
48
49! *** open file
50!	write(6,*) 'Input filename'
51!	read(5,600) filename
52	write(filename,'(a)')'Test_V2'
53	call cg_open_f(filename, MODE_READ, cg, ier)
54 	if (ier .ne. ALL_OK) call cg_error_exit_f
55	write(6,600)'READING FILE ',filename
56
57! *** CGNS Library Version used for file creation:
58	call cg_version_f(cg, version, ier)
59	if (ier .ne. ALL_OK) call cg_error_exit_f
60	write(6,102) &
61          'Library Version used for file creation:',version
62
63! *** base
64	call cg_nbases_f(cg, nbases, ier)
65	if (ier .ne. ALL_OK) call cg_error_exit_f
66	write(6,200)'nbases=',nbases
67
68	do base=1, nbases
69
70	  call cg_base_read_f(cg, base, basename, CellDim, PhysDim, ier)
71	  if (ier .ne. ALL_OK) call cg_error_exit_f
72	  write(6,300)'BaseName = "',basename,'"',  &
73                      'cell_dimension=',Celldim, &
74                      'physical_dimension=',PhysDim
75
76! *** simulation type
77	  call cg_simulation_type_read_f(cg, base, simulation, ier)
78	  if (ier .ne. ALL_OK) call cg_error_exit_f
79	  write(6,600)' Simulation Type is ', &
80                        SimulationTypeName(simulation)
81!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
82
83! *** base iterative data
84	  call cg_biter_read_f(cg, base, bitername, nsteps, ier)
85	  if (ier .eq. ERROR) call cg_error_exit_f
86	  if (ier .eq. ALL_OK) then
87	      write(6,300)' BaseIterativeData_t name ="',bitername,'"'
88	      write(6,200)'   nsteps=',nsteps
89
90        ! *** Data arrays under BaseIterativeData_t node
91	      call cg_goto_f(cg, base, ier, 'BaseIterativeData_t', &
92                             1, 'end')
93	      if (ier .ne. ALL_OK) call cg_error_exit_f
94
95              call cg_narrays_f(narrays, ier)
96              if (ier .ne. ALL_OK) call cg_error_exit_f
97              write(6,105) '   ',narrays,' DataArray_t nodes(s)'
98
99              do iarray=1,narrays
100
101              	call cg_array_info_f(iarray, arrayname, datatype, &
102                      nndim, dim_vals, ier)
103                if (ier .ne. ALL_OK) call cg_error_exit_f
104
105                write(6,108)'     DataArray_t #',iarray,':'
106                write(6,600)'       Name = ',arrayname
107                write(6,600)'       Type = ',DataTypeName(datatype)
108                write(6,104)'       Ndim=',nndim
109                num = 1
110                do i=1,nndim
111                    write(6,111)'       DataDim(',i,')=',dim_vals(i)
112                    num = num*dim_vals(i)
113                enddo
114!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
115
116                if (datatype .eq. Character) then
117                    call cg_array_read_f(iarray, data_char, ier)
118                    if (ier .ne. ALL_OK) call cg_error_exit_f
119		    if (arrayname(1:12).eq.'ZonePointers') then
120		      do step=1, nsteps
121		        do mzone=1,dim_vals(2)
122			  start = ((step-1)*dim_vals(2)+(mzone-1))*32+1
123			  end=start+32-1
124			  write(6,601)'step ',step,' zone ',mzone, &
125                                      ' is ',(data_char(i),i=start,end)
126			enddo
127		      enddo
128		    endif
129
130		else if (datatype .eq. RealSingle) then
131		    call cg_array_read_f(iarray, data_single, ier)
132		    if (ier .ne. ALL_OK) call cg_error_exit_f
133		    write(6,106)'       data=',(data_single(i),i=1,num)
134
135	        else if (datatype .eq. RealDouble) then
136                    call cg_array_read_f(iarray, data_double, ier)
137                    if (ier .ne. ALL_OK) call cg_error_exit_f
138                    write(6,106)'       data=',(data_double(i),i=1,num)
139
140		else if (datatype .eq. Integer) then
141		    call cg_array_read_f(iarray, data_int, ier)
142		    if (ier .ne. ALL_OK) call cg_error_exit_f
143		    write(6,128)'       data=',(data_int(i),i=1,num)
144                endif
145	      enddo	! loop through arrays
146	  endif		! if BaseIterativeData_t is defined
147
148! *** zone
149	  call cg_nzones_f(cg, base, nzones, ier)
150	  if (ier .ne. ALL_OK) call cg_error_exit_f
151	  write(6,200)'nzones=',nzones
152
153	  do zone=1, nzones
154
155	    call cg_zone_read_f(cg, base, zone, zonename, size, ier)
156	    if (ier .ne. ALL_OK) call cg_error_exit_f
157	    write(6,104)'Name of Zone',zone,' is "',zonename,'"'
158
159	    call cg_zone_type_f(cg, base, zone, zonetype, ier)
160	    if (ier .ne. ALL_OK) call cg_error_exit_f
161	    write(6,600)'  Zone type is ', ZoneTypeName(zonetype)
162
163	    if (zonetype.eq.Structured) then
164                 IndexDim=CellDim
165	    else
166                 IndexDim=1
167            endif
168	    write(6,104)'  IndexDimension=',IndexDim
169
170! *** zone iterative data
171            call cg_ziter_read_f(cg, base, zone, zitername, ier)
172            if (ier .eq. ERROR) call cg_error_exit_f
173            if (ier .eq. ALL_OK) then
174              write(6,300)' ZoneIterativeData_t name ="',zitername,'"'
175
176        ! *** Data arrays under BaseIterativeData_t node
177              call cg_goto_f(cg, base, ier, 'Zone_t', zone,  &
178                             'ZoneIterativeData_t', 1, 'end')
179              if (ier .ne. ALL_OK) call cg_error_exit_f
180
181              call cg_narrays_f(narrays, ier)
182              if (ier .ne. ALL_OK) call cg_error_exit_f
183              write(6,105) '   ',narrays,' DataArray_t nodes(s)'
184
185              do iarray=1,narrays
186
187                call cg_array_info_f(iarray, arrayname, datatype, &
188                      nndim, dim_vals, ier)
189                if (ier .ne. ALL_OK) call cg_error_exit_f
190
191                write(6,108)'     DataArray_t #',iarray,':'
192                write(6,600)'       Name = ',arrayname
193                write(6,600)'       Type = ',DataTypeName(datatype)
194                write(6,104)'       Ndim=',nndim
195                num = 1
196                do i=1,nndim
197                    write(6,111)'       DataDim(',i,')=',dim_vals(i)
198                    num = num*dim_vals(i)
199                enddo
200!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
201
202                if (datatype .eq. Character) then
203                    call cg_array_read_f(iarray, data_char, ier)
204                    if (ier .ne. ALL_OK) call cg_error_exit_f
205                    if (arrayname(1:23).eq.'GridCoordinatesPointers'.or. &
206                      arrayname(1:20).eq.'FlowSolutionPointers'.or. &
207                      arrayname(1:23).eq.'RigidGridMotionPointers'.or. &
208                      arrayname(1:27).eq.'ArbitraryGridMotionPointers') &
209                      then
210                      do step=1, nsteps
211                          start = (step-1)*32+1
212                          end=start+32-1
213                          write(6,602)'step ',step, &
214                                      ' is ',(data_char(i),i=start,end)
215                      enddo
216                    endif
217		endif
218              enddo     ! loop through arrays
219	    endif	! if ZoneIterativeData_t exist
220! ***
221
222! *** Multiple GridCoordinates_t Nodes
223	    call cg_ngrids_f(cg, base, zone, ngrids, ier)
224	    if (ier .ne. ALL_OK) call cg_error_exit_f
225
226            write(6,113) ngrids,' GridCoordinates_t node(s)', &
227                    'found for ',zonename
228
229!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
230	    do grid=1, ngrids
231	! *** GridCoordinates_t info
232	      call cg_grid_read_f(cg, base, zone, grid, gridname, ier)
233	      if (ier .ne. ALL_OK) call cg_error_exit_f
234
235              write(6,108)' GridCoordinates_t #',grid,':'
236              write(6,600)'   Name = ',gridname
237
238        ! *** GOTO GridCoordinates_t node
239              call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
240                             'GridCoordinates_t', grid, 'end')
241       	      if (ier .ne. ALL_OK) call cg_error_exit_f
242
243        ! *** Read coordinate arrays
244	      call cg_narrays_f(narrays, ier)
245	      if (ier .ne. ALL_OK) call cg_error_exit_f
246	      write(6,105) '   ',narrays,' DataArray_t nodes(s)'
247
248	      do iarray=1,narrays
249
250	  ! *** GridCoordinates_t attribute: DataArray_t
251                call cg_array_info_f(iarray, name, datatype, &
252                                     nndim, dim_vals, ier)
253                if (ier .ne. ALL_OK) call cg_error_exit_f
254                write(6,600)' DataArrayName="',name,'"'
255                write(6,600)' DataType=',DataTypeName(datatype)
256                write(6,104)' DataNdim=',nndim
257		do i=1,nndim
258                  write(6,111)' DataDim(',i,')=',dim_vals(i)
259		enddo
260
261	  ! *** Compute nr of data in data array:
262	   	num = 1
263		do i=1,nndim
264		  num = num*dim_vals(i)
265		enddo
266
267                if (datatype .eq. RealSingle) then
268                  call cg_array_read_f(iarray, data_single, ier)
269                  if (ier .ne. ALL_OK) call cg_error_exit_f
270                  write(6,106) 'first pts:',(data_single(i),i=1,2)
271                  write(6,106) 'last pts:',(data_single(i),i=num-1,num)
272                elseif (datatype .eq. RealDouble) then
273                  call cg_array_read_f(iarray, data_double, ier)
274                  if (ier .ne. ALL_OK) call cg_error_exit_f
275                  write(6,106) 'first pts:',(data_double(i),i=1,2)
276                  write(6,106) 'last pts:',(data_double(i),i=num-1,num)
277                endif
278
279	      enddo	! loop through data arrays
280
281	    enddo 	! loop through GridCoordinates_t nodes
282
283            write(6,400)'                             *     *     *'
284!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
285
286! *** solution
287
288	    call cg_nsols_f(cg, base, zone, nsols, ier)
289	    if (ier .ne. ALL_OK) call cg_error_exit_f
290	    write(6,113) nsols,' FlowSolution_t node(s)', &
291                    'found for ',zonename
292
293      ! *** Read solution with general cg_array_read function
294	    do sol=1, nsols
295	      call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
296                  'FlowSolution_t', sol, 'end')
297	      if (ier .ne. ALL_OK) call cg_error_exit_f
298
299	! *** FlowSolution_t attribute:  DataArray_t
300	      call cg_narrays_f(narrays, ier)
301	      if (ier .ne. ALL_OK) call cg_error_exit_f
302              write(6,108) ' FlowSolution_t #',sol, &
303                    ' contains ',narrays,' solution arrays'
304
305	! *** FlowSolution_t attribute:  GridLocation
306	      call cg_gridlocation_read_f(location, ier)
307	      if (ier .eq. ERROR) call cg_error_exit_f
308	      write(6,600)'  The solution data are recorded at the ', &
309                       GridLocationName(location)
310
311!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
312	! *** FlowSolution_t attribute:  Rind
313	      call cg_rind_read_f(rind, ier)
314              if (ier .eq. ERROR) call cg_error_exit_f
315	      write(6,103)'  The Rind Data is ',(rind(i),i=1,6)
316
317              do iarray=1,narrays
318	        call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
319                  'FlowSolution_t', sol, 'end')
320                if (ier .ne. ALL_OK) call cg_error_exit_f
321
322                call cg_array_info_f(iarray, name, datatype, &
323                                     nndim, dim_vals, ier)
324                if (ier .ne. ALL_OK) call cg_error_exit_f
325	        write(6,114) '  DataArray #',iarray
326                write(6,600) '   Name="',name,'"'
327                write(6,600) '   DataType=',DataTypeName(datatype)
328                write(6,103) '   DataNdim=',nndim
329                do i=1,nndim
330                  write(6,111)'   DataDim(',i,')=',dim_vals(i)
331                enddo
332
333                if (datatype .eq. RealSingle) then
334                  call cg_array_read_f(iarray, data_single, ier)
335                  if (ier .ne. ALL_OK) call cg_error_exit_f
336                  write(6,106) '   first pts:',(data_single(i),i=1,2)
337                elseif (datatype .eq. RealDouble) then
338                  call cg_array_read_f(iarray, data_double, ier)
339                  if (ier .ne. ALL_OK) call cg_error_exit_f
340                  write(6,106) '   first pts:',(data_double(i),i=1,2)
341                endif
342
343	      enddo	! loop through DataArray_t
344	      write(6,103)' '
345
346            enddo	! loop through FlowSolution_t
347
348            write(6,400)'                             *     *     *'
349
350
351! *** Rigid Grid Motion
352!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
353	    call cg_n_rigid_motions_f(cg, base, zone, nrmotion, ier)
354	    if (ier .ne. ALL_OK) call cg_error_exit_f
355            write(6,113) nrmotion,' RigidGridMotion_t node(s)', &
356                    'found for ',zonename
357
358	    do rmotion=1, nrmotion
359	        call cg_rigid_motion_read_f(cg, base, zone, rmotion, &
360      		    rmotionname, rmotiontype, ier)
361	        if (ier .ne. ALL_OK) call cg_error_exit_f
362
363                write(6,108)' RigidGridMotion_t #',rmotion,':'
364	        write(6,600)'   Name = ',rmotionname
365	        write(6,600)'   Type = ', &
366                             RigidGridMotionTypeName(rmotiontype)
367
368                call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
369                               'RigidGridMotion_t', rmotion, 'end')
370                if (ier .ne. ALL_OK) call cg_error_exit_f
371
372		call cg_ndescriptors_f(ndescr, ier)
373		if (ier .ne. ALL_OK) call cg_error_exit_f
374		write(6,105) '   ',ndescr, ' Descriptor_t node(s)'
375
376		do descr=1, ndescr
377		    call cg_descriptor_read_f(descr, descrname,  &
378                         descrtext, ier)
379		    if (ier .ne. ALL_OK) call cg_error_exit_f
380		    write(6,108)'     Descriptor_t #',descr,':'
381		    write(6,600)'       Name = ',descrname
382		    write(6,600)'       Text = ',descrtext
383		enddo
384
385!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
386! *** Data arrays under RigidGridMotion_t node
387	        call cg_narrays_f(narrays, ier)
388	        if (ier .ne. ALL_OK) call cg_error_exit_f
389		write(6,105) '   ',narrays,' DataArray_t nodes(s)'
390
391		do iarray=1,narrays
392		    call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
393                               'RigidGridMotion_t', rmotion, 'end')
394
395		    call cg_array_info_f(iarray, arrayname, datatype, &
396                      nndim, dim_vals, ier)
397		    if (ier .ne. ALL_OK) call cg_error_exit_f
398
399		    write(6,108)'     DataArray_t #',iarray,':'
400		    write(6,600)'       Name = ',arrayname
401		    write(6,600)'       Type = ',DataTypeName(datatype)
402                    write(6,104)'       Ndim=',nndim
403                    num = 1
404                    do i=1,nndim
405                        write(6,111)'       DataDim(',i,')=',dim_vals(i)
406			num = num*dim_vals(i)
407                    enddo
408!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
409
410                    if (datatype .eq. RealSingle) then
411                        call cg_array_read_f(iarray, data_single, ier)
412                        if (ier .ne. ALL_OK) call cg_error_exit_f
413                  	write(6,106)'       first pts:', &
414                                     (data_single(i),i=1,dim_vals(1))
415		    else if (datatype .eq. RealDouble) then
416			call cg_array_read_f(iarray, data_double, ier)
417		  	if (ier .ne. ALL_OK) call cg_error_exit_f
418			write(6,106)'       first pts:', &
419                                     (data_double(i),i=1,dim_vals(1))
420		    endif
421
422		    call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
423                               'RigidGridMotion_t', rmotion, &
424                               'DataArray_t', iarray, 'end')
425		    if (ier .ne. ALL_OK) call cg_error_exit_f
426
427!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
428		    call cg_units_read_f(mass,length,time,temp,deg,ier)
429              	    if (ier .eq. ERROR) call cg_error_exit_f
430              	    if (ier .eq. ALL_OK) then
431                	write(6,100) &
432                  	'       Dimensional Units:', &
433                  	MassUnitsName(mass), LengthUnitsName(length), &
434                  	TemperatureUnitsName(temp), TimeUnitsName(time), &
435                  	AngleUnitsName(deg)
436		    endif
437		enddo	! loop through data arrays
438	    enddo	! loop through rmotion
439            write(6,400)'                             *     *     *'
440
441
442! *** Read arbitrary grid motion
443!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
444            call cg_n_arbitrary_motions_f(cg, base, zone, namotion, ier)
445            if (ier .ne. ALL_OK) call cg_error_exit_f
446            write(6,113) namotion,' ArbitraryGridMotion_t node(s)', &
447                    'found for ',zonename
448
449            do amotion=1, namotion
450                call cg_arbitrary_motion_read_f(cg, base, zone, amotion, &
451                    amotionname, amotiontype, ier)
452                if (ier .ne. ALL_OK) call cg_error_exit_f
453
454                write(6,108)' ArbitraryGridMotion_t #',amotion,':'
455                write(6,600)'   Name = ',amotionname
456                write(6,600)'   Type = ', &
457                             ArbitraryGridMotionTypeName(amotiontype)
458!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
459
460                call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
461                           'ArbitraryGridMotion_t', amotion, 'end')
462                if (ier .ne. ALL_OK) call cg_error_exit_f
463
464                call cg_ndescriptors_f(ndescr, ier)
465                if (ier .ne. ALL_OK) call cg_error_exit_f
466                write(6,105) '   ',ndescr, ' Descriptor_t node(s)'
467
468                do descr=1, ndescr
469                    call cg_descriptor_read_f(descr, descrname, &
470                         descrtext, ier)
471                    if (ier .ne. ALL_OK) call cg_error_exit_f
472                    write(6,108)'     Descriptor_t #',descr,':'
473                    write(6,600)'       Name = ',descrname
474                    write(6,600)'       Text = ',descrtext
475                enddo
476!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
477! *** Data arrays under ArbitraryGridMotion_t node
478                call cg_narrays_f(narrays, ier)
479                if (ier .ne. ALL_OK) call cg_error_exit_f
480                write(6,105) '   ',narrays,' DataArray_t nodes(s)'
481
482                do iarray=1,narrays
483                    call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
484                           'ArbitraryGridMotion_t', amotion, 'end')
485
486                    call cg_array_info_f(iarray, arrayname, datatype, &
487                      nndim, dim_vals, ier)
488                    if (ier .ne. ALL_OK) call cg_error_exit_f
489
490                    write(6,108)'     DataArray_t #',iarray,':'
491                    write(6,600)'       Name = ',arrayname
492                    write(6,600)'       Type = ',DataTypeName(datatype)
493                    write(6,104)'       Ndim=',nndim
494                    num = 1
495                    do i=1,nndim
496                        write(6,111)'       DataDim(',i,')=',dim_vals(i)
497                        num = num*dim_vals(i)
498                    enddo
499!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
500
501                    if (datatype .eq. RealSingle) then
502                        call cg_array_read_f(iarray, data_single, ier)
503                        if (ier .ne. ALL_OK) call cg_error_exit_f
504                        write(6,106)'       first pts:', &
505                                     (data_single(i),i=1,dim_vals(1))
506		    else if (datatype .eq. RealDouble) then
507                        call cg_array_read_f(iarray, data_double, ier)
508                        if (ier .ne. ALL_OK) call cg_error_exit_f
509                        write(6,106)'       first pts:', &
510                                     (data_double(i),i=1,dim_vals(1))
511                    endif
512
513                    call cg_goto_f(cg, base, ier, 'Zone_t', zone, &
514                           'ArbitraryGridMotion_t', amotion, &
515                               'DataArray_t', iarray, 'end')
516                    if (ier .ne. ALL_OK) call cg_error_exit_f
517
518!234567890!234567890!234567890!234567890!234567890!234567890!23456789012
519                    call cg_units_read_f(mass,length,time,temp,deg,ier)
520                    if (ier .eq. ERROR) call cg_error_exit_f
521                    if (ier .eq. ALL_OK) then
522                        write(6,100) &
523                        '       Dimensional Units:', &
524                        MassUnitsName(mass), LengthUnitsName(length), &
525                        TemperatureUnitsName(temp), TimeUnitsName(time), &
526                        AngleUnitsName(deg)
527                    endif
528                enddo   ! loop through data arrays
529            enddo       ! loop through amotion
530            write(6,400)'                             *     *     *'
531	  enddo					! loop through zones
532 	enddo    				! loop through bases
533
534        call cg_close_f(cg, ier)
535        if (ier .eq. ERROR) call cg_error_exit_f
536
537 100 	format(a/,'        Mass units: ',a/, &
538                  '        Length units: ',a/, &
539                  '        Temperature units: ',a/, &
540                  '        Time units: ',a/, &
541                  '        Angle units:',a)
542 101	format(a,i1,a,/2a,/2a,/2a,/3a,/a,i4,3a,/2a,/2a,/2a,/a,i4)
543 102 	format(a,f5.3)
544 103	format(a,6i2)
545 104	format(a,i2,3a)
546 105	format(a,i2,a)
547 106    format(a,6f10.3)
548 107	format(i2,2a)
549 108    format(a,i2,a,i2,a)
550 109	format(a,f5.1)
551 110	format(a,5f5.1)
552 111	format(a,i1,a,i8)
553 112	format(a,i1/2a/3a)
554 113	format(i1,3a)
555 114	format(/a, i1)
556 115	format(a,i1,a/3a/2a)
557 116	format(a,i1,a,i1,a)
558 117	format(/i4,2a)
559 118	format(a,i1,a/3a/2a/a,i1,a,i5)
560 119	format(a/a,3i2/a,3i2)
561 120	format(a10, 3(a1,i1),a6,3(i1,a1))
562 121 	format(a16,3(a1,i1),a6,3(i1,a1))
563 122	format(a12,3(a1,i2),a1)
564 124	format(4x, f7.2)
565 126	format(a/a,3f5.2/a,3f5.2)
566 127	format(2a,i1,a)
567 128	format(a,6i5)
568 130	format(a15, i2, a4)
569 131	format(a10, 3(a1,i1),a6,3(i1,a1))
570 132	format(a16,3(a1,i1),a6,3(i1,a1))
571 133	format(a12,3(a1,i2),a1)
572 134	format(a,6f6.2)
573 200    format(a,i3)
574 300	format(3a/a,i2,/a,i2)
575 400	format(/a/)
576 401	format(/2a/)
577 500	format(3a/3a)
578 600	format(3a)
579 601	format(7x,a,i2,a,i2,33a)
580 602	format(7x,a,i2,33a)
581
582 	end
583