KTH framework for Nek5000 toolboxes; testing version  0.0.1
arna_io.f
Go to the documentation of this file.
1 
4 !=======================================================================
7  subroutine arna_rst_save
8  implicit none
9 
10  include 'SIZE' ! NIO
11  include 'TSTEP' ! LASTEP
12  include 'FRAMELP'
13  include 'TSTPRD'
14  include 'ARNAD'
15 
16  ! local variables
17  character(20) str
18 !-----------------------------------------------------------------------
19  ! save checkpoint for idoarp=-2
20  if (idoarp.eq.-2) then
21  call mntr_logi(arna_id,lp_prd,
22  $ 'Writing checkpoint; ido = ',idoarp)
23 
24  ! save parameters and workla; independent on processor;
25  ! serial output
26  call arna_write_par('ARP')
27 
28  ! save big arrays; parallel output
29  call arna_mfov('ARV')
30 
31  ! this is the last step
32  lastep=1
33  endif
34 
35  return
36  end
37 !=======================================================================
40  subroutine arna_rst_read
41  implicit none
42 
43  include 'SIZE' ! NIO
44  include 'FRAMELP'
45  include 'TSTPRD'
46  include 'ARNAD'
47 !-----------------------------------------------------------------------
48  call mntr_log(arna_id,lp_prd,
49  $ 'Reading checkpoint.')
50 
51  ! read parameters and WORKLA; independent on processor; serial input
52  call arna_read_par('ARP')
53 
54  ! read big arrays; parallel input
55  call arna_mfiv('ARV')
56 
57  return
58  end
59 !=======================================================================
63  subroutine arna_write_par(prefix)
64  implicit none
65 
66  include 'SIZE'
67  include 'INPUT'
68  include 'RESTART'
69  include 'TSTEP'
70  include 'FRAMELP'
71  include 'TSTPRD'
72  include 'ARNAD'
73 
74  ! argument list
75  character*3 prefix
76 
77  ! local variables
78  character*132 fname
79  character*6 str
80  integer lwdsizo, lfid0, ierr
81  logical lifreguo, lifmpiio
82 !-----------------------------------------------------------------------
83  call nekgsync()
84  call io_init()
85 
86  ! copy and set output parameters
87  lwdsizo= wdsizo
88  wdsizo = 8
89 
90  lifreguo= ifreguo
91  ifreguo = .false.
92 
93  ! this is done by master node only, so serial writing
94  lifmpiio = ifmpiio
95  ifmpiio = .false.
96  lfid0 = fid0
97  fid0 = 0
98 
99  ierr = 0
100  if (nid.eq.0) then
101  ! create file name
102  call io_mfo_fname(fname,session,prefix,ierr)
103  if (ierr.eq.0) then
104  write(str,'(i5.5)') mod(arna_fnum,2) + 1
105  fname = trim(fname)//trim(str)
106  ! open file
107  call io_mbyte_open(fname,ierr)
108  endif
109 
110  if (ierr.eq.0) then
111  call arna_mfop
112  ! close the file; only serial
113  call byte_close(ierr)
114  endif
115  endif
116 
117  call mntr_check_abort(arna_id,ierr,
118  $ 'arna_write_par: Error writing par file.')
119 
120  ! put output variables back
121  wdsizo = lwdsizo
122  ifreguo = lifreguo
123  ifmpiio = lifmpiio
124  fid0 = lfid0
125 
126  return
127  end
128 !=======================================================================
131  subroutine arna_mfop
132  implicit none
133 
134  include 'SIZE'
135  include 'TSTEP'
136  include 'TSTPRD'
137  include 'ARNAD'
138 
139  ! local variables
140  character*16 hdr
141  integer ahdsize
142  parameter(ahdsize=16)
143 
144  integer il, itmp(33), ierr
145 
146  real*4 test_pattern
147 
148  real*4 rtmp4(6), workla4(2*wldima)
149  real*8 rtmp8(3), workla8(wldima)
150  equivalence(rtmp4,rtmp8)
151  equivalence(workla4,workla8)
152 !-----------------------------------------------------------------------
153  ! write idoarp and character varialbes
154  call blank(hdr,ahdsize)
155 
156  write(hdr,1) idoarp,bmatarp,whicharp,tstpr_mode! 14
157  1 format('#arp',1x,i2,1x,a1,1x,a2,1x,i1)
158 
159  call byte_write(hdr,ahdsize/4,ierr)
160 
161  ! write test pattern for byte swap
162  test_pattern = 6.54321
163 
164  call byte_write(test_pattern,1,ierr)
165 
166  ! collect and write integer varialbes
167  itmp(1) = arna_ns
168  itmp(2) = arna_negv
169  itmp(3) = arna_nkrl
170  itmp(4) = nwlarp
171  itmp(5) = infarp
172  itmp(6) = nparp
173  itmp(7) = ncarp
174  itmp(8) = tstpr_step
175  do il=1,11
176  itmp(8+il) = iparp(il)
177  enddo
178  do il=1,14
179  itmp(19+il) = ipntarp(il)
180  enddo
181 
182  call byte_write(itmp,33,ierr)
183 
184  ! collect and write real variables
185  rtmp8(1) = tstpr_tol
186  rtmp8(2) = rnmarp
187  rtmp8(3) = dt
188 
189  call byte_write(rtmp4,6,ierr)
190 
191  ! write workla
192  call copy(workla8,workla,nwlarp)
193 
194  call byte_write(workla4,2*nwlarp,ierr)
195 
196  return
197  end
198 !=======================================================================
202  subroutine arna_read_par(prefix)
203  implicit none
204 
205  include 'SIZE'
206  include 'INPUT'
207  include 'RESTART'
208  include 'TSTEP'
209  include 'PARALLEL'
210  include 'FRAMELP'
211  include 'TSTPRD'
212  include 'ARNAD'
213 
214  ! argument list
215  character*3 prefix
216 
217  ! local variables
218  character*132 fname
219  character*6 str
220  integer lwdsizo, lfid0, ierr, il
221  logical lifreguo, lifmpiio
222 !-----------------------------------------------------------------------
223  call nekgsync()
224  call io_init()
225 
226  !copy and set output parameters
227  lwdsizo= wdsizo
228  wdsizo = 8
229 
230  lifreguo= ifreguo
231  ifreguo = .false.
232 
233  ! this is done by master node only, so serial reading
234  lifmpiio = ifmpiio
235  ifmpiio = .false.
236  lfid0 = fid0
237  fid0 = 0
238 
239  ierr = 0
240  if (nid.eq.0) then
241  ! create file name
242  call io_mfo_fname(fname,session,prefix,ierr)
243  if (ierr.eq.0) then
244  write(str,'(i5.5)') arna_fnum
245  fname = trim(fname)//trim(str)
246  ! open file
247  call io_mbyte_open(fname, ierr)
248  endif
249 
250  if (ierr.eq.0) then
251  ! read parameters
252  call arna_mfip
253  ! close the file
254  call byte_close(ierr)
255  endif
256  endif
257 
258  call mntr_check_abort(arna_id,ierr,
259  $ 'arna_read_par: Error opening par file.')
260 
261  ierr = 0
262  if (nid.eq.0) then
263  ! check and copy parameters
264  ! is it correct restart
265  if (idoarp0.ne.-2) then
266  call mntr_error(arna_id,
267  $ 'arna_read_par, wrong idoarp0')
268  call mntr_logi(arna_id,lp_err,'idoarp0 = ', idoarp0)
269  ierr=1
270  endif
271 
272  ! is it the same ARPACK mode
273  if (bmatarp0.ne.bmatarp) then
274  call mntr_error(arna_id,
275  $ 'arna_read_par, different ARPACK modes')
276  call mntr_logi(arna_id,lp_err,'bmatarp0 = ', bmatarp0)
277  call mntr_logi(arna_id,lp_err,'bmatarp = ', bmatarp)
278  ierr=1
279  endif
280 
281  ! do we look for the same eigenvectors
282  if (whicharp0.ne.whicharp) then
283  call mntr_error(arna_id,
284  $ 'arna_read_par, different mode selsction')
285  call mntr_logi(arna_id,lp_err,'whicharp0 = ', whicharp0)
286  call mntr_logi(arna_id,lp_err,'whicharp = ', whicharp)
287  ierr=1
288  endif
289 
290  ! is it the same integration mode
291  if (tstpr_mode0.ne.tstpr_mode) then
292  call mntr_error(arna_id,
293  $ 'arna_read_par, wrong simulation mode')
294  call mntr_logi(arna_id,lp_err,'tstpr_mode0 = ',tstpr_mode0)
295  call mntr_logi(arna_id,lp_err,'tstpr_mode = ',tstpr_mode)
296  ierr=1
297  endif
298 
299  ! this should be removed later as it does not allow to change processor number
300  ! is the length of the vector the same
301  if (arna_ns0.ne.arna_ns) then
302  call mntr_error(arna_id,
303  $ 'arna_read_par, different vector length (IFHEAT?)')
304  call mntr_logi(arna_id,lp_err,'arna_ns0 = ', arna_ns0)
305  call mntr_logi(arna_id,lp_err,'arna_ns = ', arna_ns)
306  ierr=1
307  endif
308 
309  ! what is the size of krylov space
310  ! would it be possible to change this?; related nparp, nwlarp,
311  ! ipntarp
312  if (arna_nkrl0.ne.arna_nkrl) then
313  call mntr_error(arna_id,
314  $ 'arna_read_par, different Krylov space size')
315  call mntr_logi(arna_id,lp_err,'arna_nkrl0 = ', arna_nkrl0)
316  call mntr_logi(arna_id,lp_err,'arna_nkrl = ', arna_nkrl)
317  ierr=1
318  endif
319 
320  if (nwlarp0.ne.nwlarp) then
321  call mntr_error(arna_id,
322  $ 'arna_read_par, different size of work array')
323  call mntr_logi(arna_id,lp_err,'nwlarp0 = ', nwlarp0)
324  call mntr_logi(arna_id,lp_err,'nwlarp = ', nwlarp)
325  ierr=1
326  endif
327 
328  ! stopping criterion
329  if (tstpr_tol0.ne.tstpr_tol) then
330  call mntr_warn(arna_id,
331  $ 'arna_read_par, different stopping criterion')
332  call mntr_logi(arna_id,lp_err,'tstpr_tol0 = ', tstpr_tol0)
333  call mntr_logi(arna_id,lp_err,'tstpr_tol = ', tstpr_tol)
334  endif
335 
336  ! number of eigenvalues
337  if (arna_negv0.ne.arna_negv) then
338  call mntr_warn(arna_id,
339  $ 'arna_read_par, different number of eigenvalues')
340  call mntr_logi(arna_id,lp_err,'arna_negv0 = ', arna_negv0)
341  call mntr_logi(arna_id,lp_err,'arna_negv = ', arna_negv)
342  endif
343 
344  ! stepper phase length
345  if (dtarp0.ne.dt) then
346  call mntr_warn(arna_id,
347  $ 'arna_read_par, different time step')
348  call mntr_logi(arna_id,lp_err,'dtarp0 = ', dtarp0)
349  call mntr_logi(arna_id,lp_err,'dt = ', dt)
350  endif
351 
352  if (tstpr_step0.ne.tstpr_step) then
353  call mntr_warn(arna_id,
354  $ 'arna_read_par, different number of steps instepper phase')
355  call mntr_logi(arna_id,lp_err,'tstpr_step0 = ',tstpr_step0)
356  call mntr_logi(arna_id,lp_err,'tstpr_step = ',tstpr_step)
357  endif
358 
359  ! check IPARP
360  if (iparp0(1).ne.iparp(1)) then
361  call mntr_error(arna_id,
362  $ 'arna_read_par, different shift in ARPACK')
363  call mntr_logi(arna_id,lp_err,'iparp0(1) = ', iparp0(1))
364  call mntr_logi(arna_id,lp_err,'iparp(1) = ', iparp(1))
365  ierr=1
366  endif
367 
368  if (iparp0(3).ne.iparp(3)) then
369  call mntr_warn(arna_id,
370  $ 'arna_read_par, different cycle number')
371  call mntr_logi(arna_id,lp_err,'iparp0(3) = ', iparp0(3))
372  call mntr_logi(arna_id,lp_err,'iparp(3) = ', iparp(3))
373  endif
374 
375  if (iparp0(7).ne.iparp(7)) then
376  call mntr_error(arna_id,
377  $ 'arna_read_par, different ARPACK modes')
378  call mntr_logi(arna_id,lp_err,'iparp0(7) = ', iparp0(7))
379  call mntr_logi(arna_id,lp_err,'iparp(7) = ', iparp(7))
380  ierr=1
381  endif
382 
383  ! copy rest of parameters
384  nparp = nparp0
385  ncarp = ncarp0
386  infarp= infarp0
387  rnmarp= rnmarp0
388  do il=4,11
389  iparp(il) = iparp0(il)
390  enddo
391  iparp(2) = iparp0(2)
392  do il=1,14
393  ipntarp(il) = ipntarp0(il)
394  enddo
395  endif ! NID
396 
397  call mntr_check_abort(arna_id,ierr,
398  $ 'arna_read_par: Error reading par file.')
399 
400  idoarp = -2
401  ! broadcast
402  call bcast(nparp,isize)
403  call bcast(ncarp,isize)
404  call bcast(infarp,isize)
405  call bcast(iparp,11*isize)
406  call bcast(ipntarp,14*isize)
407  call bcast(rnmarp,wdsize)
408 
409  call bcast(workla,nwlarp*wdsize)
410 
411  ! put output variables back
412  wdsizo = lwdsizo
413  ifreguo = lifreguo
414 
415  return
416  end
417 !=======================================================================
420  subroutine arna_mfip
421  implicit none
422 
423  include 'SIZE'
424  include 'INPUT'
425  include 'PARALLEL'
426  include 'RESTART'
427  include 'TSTEP'
428  include 'FRAMELP'
429  include 'TSTPRD'
430  include 'ARNAD'
431 
432  ! local variables
433  character*16 hdr
434  character*4 dummy
435  integer ahdsize
436  parameter(ahdsize=16)
437 
438  integer ibsw_out, il, itmp(33), ierr
439 
440  real*4 test_pattern
441 
442  real*4 rtmp4(6), workla4(2*wldima)
443  real*8 rtmp8(3), workla8(wldima)
444  equivalence(rtmp4,rtmp8)
445  equivalence(workla4,workla8)
446 
447  logical if_byte_swap_test, if_byte_sw_loc
448 
449  ! functions
450  integer indx2
451 !-----------------------------------------------------------------------
452  ! read idoarp and character varialbes
453  call blank(hdr,ahdsize)
454 
455  call byte_read(hdr,ahdsize/4,ierr)
456 
457  if (indx2(hdr,132,'#arp',4).eq.1) then
458  read(hdr,*) dummy,idoarp0,bmatarp0,whicharp0,tstpr_mode0! 14
459  else
460  call mntr_abort(arna_id,
461  $ 'arna_mfip; Error reading header')
462  endif
463 
464  ! read test pattern for byte swap
465  call byte_read(test_pattern,1,ierr)
466  ! determine endianess
467  if_byte_sw_loc = if_byte_swap_test(test_pattern,ierr)
468 
469  ! read integer varialbes
470  call byte_read(itmp,33,ierr)
471  if (if_byte_sw) call byte_reverse(itmp,33,ierr)
472 
473  arna_ns0 = itmp(1)
474  arna_negv0 = itmp(2)
475  arna_nkrl0 = itmp(3)
476  nwlarp0 = itmp(4)
477  infarp0 = itmp(5)
478  nparp0 = itmp(6)
479  ncarp0 = itmp(7)
480  tstpr_step0 = itmp(8)
481  do il=1,11
482  iparp0(il) = itmp(8+il)
483  enddo
484  do il=1,14
485  ipntarp0(il) = itmp(19+il)
486  enddo
487 
488  ! read real variables
489  call byte_read(rtmp4,6,ierr)
490  if (if_byte_sw) call byte_reverse(rtmp4,6,ierr)
491 
492  tstpr_tol0 = rtmp8(1)
493  rnmarp0 = rtmp8(2)
494  dtarp0 = rtmp8(3)
495 
496  ! read workla
497  if (nwlarp0.le.wldima) then
498  call byte_read(workla4,2*nwlarp0,ierr)
499  if (if_byte_sw) call byte_reverse(workla4,2*nwlarp0,ierr)
500  call copy(workla,workla8,nwlarp0)
501  else
502  call mntr_abort(arna_id,
503  $ .le.'arna_mfip; Wrong work array size nwlarp0wldima')
504  endif
505 
506  return
507  end subroutine
508 !=======================================================================
513  subroutine arna_mfov(prefix) ! muti-file output
514  implicit none
515 
516  include 'SIZE'
517  include 'INPUT'
518  include 'PARALLEL'
519  include 'TSTEP'
520  include 'RESTART'
521  include 'FRAMELP'
522  include 'TSTPRD'
523  include 'ARNAD'
524 
525  ! argument list
526  character*3 prefix
527 
528  ! local variables
529  integer*8 offs0,offs,nbyte,stride,strideB,nxyzo8
530  integer lwdsizo, il, ierr
531  integer ioflds, nout
532  real dnbyte, tio, tiostart
533  character*132 fname
534  character*6 str
535  logical lifxyo, lifpo, lifvo, lifto, lifreguo, lifpso(LDIMT1)
536 
537  ! functions
538  real dnekclock_sync, glsum
539 
540  ! scratch space
541  real UR1(LXO*LXO*LXO*LELT), UR2(LXO*LXO*LXO*LELT),
542  $ UR3(LXO*LXO*LXO*LELT)
543  common /scruz/ ur1, ur2, ur3
544 !-----------------------------------------------------------------------
545  tiostart=dnekclock_sync()
546  call io_init
547 
548  ! set array and elelemnt size
549  nout = nelt
550  nxo = nx1
551  nyo = ny1
552  nzo = nz1
553 
554  ! copy and set output parameters
555  lwdsizo= wdsizo
556  wdsizo = 8
557 
558  lifreguo= ifreguo
559  ifreguo = .false.
560  lifxyo= ifxyo
561  ifxyo = .false.
562  lifpo= ifpo
563  ifpo = .false.
564  lifvo= ifvo
565  ifvo = .true.
566  lifto= ifto
567  ifto = .false.
568  do il=1,ldimt1
569  lifpso(il)= ifpso(il)
570  ifpso(il) = .false.
571  enddo
572 
573  ! open files on i/o nodes
574  ierr = 0
575  if (nid.eq.pid0) then
576  ! create file name
577  call io_mfo_fname(fname,session,prefix,ierr)
578  if (ierr.eq.0) then
579  write(str,'(i5.5)') mod(arna_fnum,2) + 1
580  fname = trim(fname)//trim(str)
581  call io_mbyte_open(fname,ierr)
582  endif
583  endif
584 
585  call mntr_check_abort(arna_id,ierr,'arna_mfov; file not opened.')
586 
587  ! write a header and create element mapping
588  call mfo_write_hdr
589 
590  ! set offset
591  offs0 = iheadersize + 4 + isize*nelgt
592  nxyzo8 = nxo*nyo*nzo
593  strideb = nelb * nxyzo8*wdsizo
594  stride = nelgt* nxyzo8*wdsizo
595  ioflds = 0
596 
597  ! dump all fields based on the t-mesh to avoid different
598  ! topologies in the post-processor
599 
600  ! resid array
601  call arna_mfosv(ioflds,nout,offs0,stride,strideb,
602  $ ur1,ur2,ur3,resida)
603 
604  ! workd array
605  do il=0,2
606  call arna_mfosv(ioflds,nout,offs0,stride,strideb,
607  $ ur1,ur2,ur3,workda(1+arna_ns*il))
608  enddo
609 
610  ! krylov space
611  do il=1,arna_nkrl
612  call arna_mfosv(ioflds,nout,offs0,stride,strideb,
613  $ ur1,ur2,ur3,vbasea(1,il))
614  enddo
615 
616  dnbyte = 1.*ioflds*nout*wdsizo*nxo*nyo*nzo
617 
618  ! put output variables back
619  wdsizo = lwdsizo
620 
621  ifreguo = lifreguo
622  ifxyo = lifxyo
623  ifpo = lifpo
624  ifvo = lifvo
625  ifto = lifto
626  do il=1,ldimt1
627  ifpso(il) = lifpso(il)
628  enddo
629 
630  call io_mbyte_close(ierr)
631  call mntr_check_abort(arna_id,ierr,'arna_mfov; file not closed.')
632 
633  ! stamp the log
634  tio = dnekclock_sync()-tiostart
635  if (tio.le.0) tio=1.
636 
637  dnbyte = glsum(dnbyte,1)
638  dnbyte = dnbyte + iheadersize + 4. + isize*nelgt
639  dnbyte = dnbyte/1024/1024
640 
641  call mntr_log(arna_id,lp_prd,'Checkpoint written:')
642  call mntr_logr(arna_id,lp_vrb,'file size (MB) = ',dnbyte)
643  call mntr_logr(arna_id,lp_vrb,'avg data-throughput (MB/s) = ',
644  $ dnbyte/tio)
645  call mntr_logi(arna_id,lp_vrb,'io-nodes = ',nfileo)
646 
647  return
648  end
649 !=======================================================================
654  subroutine arna_mfiv(prefix)
655  implicit none
656 
657  include 'SIZE'
658  include 'PARALLEL'
659  include 'INPUT'
660  include 'TSTEP'
661  include 'RESTART'
662  include 'FRAMELP'
663  include 'TSTPRD'
664  include 'ARNAD'
665 
666  ! argument list
667  character*3 prefix
668 
669  ! local variables
670  character*132 fname
671 
672  character*6 str
673 
674  integer e, il, iofldsr, ierr
675  integer*8 offs0,offs,nbyte,stride,strideB,nxyzr8
676  real dnbyte, tio, tiostart
677 
678  ! functions
679  real dnekclock_sync, glsum
680 
681  ! scratch space
682  integer lwk
683  parameter(lwk = 7*lx1*ly1*lz1*lelt)
684  real wk(lwk)
685  common /scrns/ wk
686 
687  real UR1(LX1,LY1,LZ1,LELT), UR2(LX1,LY1,LZ1,LELT),
688  $ UR3 (LX1,LY1,LZ1,LELT)
689  COMMON /scruz/ ur1, ur2, ur3
690 !-----------------------------------------------------------------------
691  tiostart=dnekclock_sync()
692  call io_init
693 
694  ! create file name
695  ierr = 0
696  if (nid.eq.pid0r) then ! open files on i/o nodes
697  call io_mfo_fname(fname,session,prefix,ierr)
698  if (ierr.eq.0) then
699  write(str,'(i5.5)') arna_fnum
700  fname = trim(fname)//trim(str)
701  endif
702  endif
703 
704  call mntr_check_abort(arna_id,ierr,'arna_mfiv; file not opened.')
705 
706  call mfi_prepare(fname) ! determine reader nodes +
707  ! read hdr + element mapping
708 
709  offs0 = iheadersize + 4 + isize*nelgr
710  nxyzr8 = nxr*nyr*nzr
711  strideb = nelbr* nxyzr8*wdsizr
712  stride = nelgr* nxyzr8*wdsizr
713 
714  ! read arrays
715  iofldsr = 0
716 
717  ! resid array
718  call arna_mfisv(iofldsr,offs0,stride,strideb,
719  $ ur1,ur2,ur3,resida(1))
720 
721  ! workd array
722  do il=0,2
723  call arna_mfisv(iofldsr,offs0,stride,strideb,
724  $ ur1,ur2,ur3,workda(1+arna_ns*il))
725  enddo
726 
727  ! krylov space
728  do il=1,arna_nkrl
729  call arna_mfisv(iofldsr,offs0,stride,strideb,
730  $ ur1,ur2,ur3,vbasea(1,il))
731  enddo
732 
733  ! close files
734  call io_mbyte_close(ierr)
735  call mntr_check_abort(arna_id,ierr,'arna_mfiv; file not closed.')
736 
737  ! stamp the log
738  tio = dnekclock_sync()-tiostart
739  if (tio.le.0) tio=1.
740 
741  if(nid.eq.pid0r) then
742  dnbyte = 1.*iofldsr*nelr*wdsizr*nxr*nyr*nzr
743  else
744  dnbyte = 0.0
745  endif
746 
747  dnbyte = glsum(dnbyte,1)
748  dnbyte = dnbyte + iheadersize + 4. + isize*nelgt
749  dnbyte = dnbyte/1024/1024
750 
751  call mntr_log(arna_id,lp_prd,'Checkpoint read:')
752  call mntr_logr(arna_id,lp_vrb,'avg data-throughput (MB/s) = ',
753  $ dnbyte/tio)
754  call mntr_logi(arna_id,lp_vrb,'io-nodes = ',nfileo)
755 
756  return
757  end subroutine
758 !=======================================================================
768  subroutine arna_mfosv(ioflds,nout,offs0,stride,strideB,
769  $ ur1,ur2,ur3,vect)
770  implicit none
771 
772  include 'SIZE'
773  include 'INPUT' ! IF3D, IFHEAT
774  include 'RESTART'
775  include 'TSTPRD'
776  include 'ARNAD'
777 
778  ! argument list
779  integer ioflds,nout
780  integer*8 offs0,stride,strideB
781  real UR1(LXO*LXO*LXO*LELT), UR2(LXO*LXO*LXO*LELT),
782  $ ur3(lxo*lxo*lxo*lelt)
783  real VECT(arna_ls)
784 
785  ! local variables
786  integer*8 offs
787 !-----------------------------------------------------------------------
788  offs = offs0 + ioflds*stride + ndim*strideb
789  call byte_set_view(offs,ifh_mbyte)
790 
791  call copy(ur1,vect(1),tstpr_nv)
792  call copy(ur2,vect(1+tstpr_nv),tstpr_nv)
793  if (if3d) call copy(ur3,vect(1+2*tstpr_nv),tstpr_nv)
794 
795  call mfo_outv(ur1,ur2,ur3,nout,nxo,nyo,nzo)
796  ioflds = ioflds + ndim
797 
798  if (ifheat) then
799  offs = offs0 + ioflds*stride + strideb
800  call byte_set_view(offs,ifh_mbyte)
801  call copy(ur1,vect(1+ndim*tstpr_nv),tstpr_nt)
802 
803  call mfo_outs(ur1,nout,nxo,nyo,nzo)
804  ioflds = ioflds + 1
805  endif
806 
807  return
808  end subroutine
809 !=======================================================================
819  subroutine arna_mfisv(iofldr,offs0,stride,strideB,
820  $ ur1,ur2,ur3,vect)
821  implicit none
822 
823  include 'SIZE'
824  include 'INPUT' ! IF3D, IFHEAT
825  include 'RESTART'
826  include 'TSTPRD'
827  include 'ARNAD'
828 
829  ! argument list
830  integer iofldr
831  integer*8 offs0,stride,strideB
832  real UR1(LX1*LX1*LX1*LELT), UR2(LX1*LX1*LX1*LELT),
833  $ ur3(lx1*lx1*lx1*lelt)
834  real VECT(arna_ls)
835 
836  integer lwk
837  parameter (lwk = 7*lx1*ly1*lz1*lelt)
838  real wk(lwk)
839  common /scrns/ wk
840 
841  ! local variables
842  integer*8 offs
843 !-----------------------------------------------------------------------
844  offs = offs0 + iofldr*stride + ndim*strideb
845  call byte_set_view(offs,ifh_mbyte)
846  call mfi_getv(ur1,ur2,ur3,wk,lwk,.false.)
847 
848  call copy(vect(1),ur1,tstpr_nv)
849  call copy(vect(1+tstpr_nv),ur2,tstpr_nv)
850  if (if3d) call copy(vect(1+2*tstpr_nv),ur3,tstpr_nv)
851  iofldr = iofldr + ndim
852 
853  if (ifheat) then
854  offs = offs0 + iofldr*stride + strideb
855  call byte_set_view(offs,ifh_mbyte)
856  call mfi_gets(ur1,wk,lwk,.false.)
857 
858  call copy(vect(1+ndim*tstpr_nv),ur1,tstpr_nt)
859  iofldr = iofldr + 1
860  endif
861 
862  return
863  end subroutine
864 !=======================================================================
#define byte_reverse
Definition: byte.c:33
#define byte_write
Definition: byte.c:39
#define byte_close
Definition: byte.c:36
#define byte_read
Definition: byte.c:38
subroutine byte_set_view(ioff_in, mpi_fh)
Definition: byte_mpi.f:97
subroutine nekgsync()
Definition: comm_mpi.f:502
subroutine bcast(buf, len)
Definition: comm_mpi.f:431
subroutine arna_mfip
Read procesor independent variables.
Definition: arna_io.f:421
subroutine arna_mfov(prefix)
Write procesor dependent data (long vectors)
Definition: arna_io.f:514
subroutine arna_write_par(prefix)
Write procesor independent data.
Definition: arna_io.f:64
subroutine arna_mfiv(prefix)
Read procesor dependent data (long vectors)
Definition: arna_io.f:655
subroutine arna_mfisv(iofldr, offs0, stride, strideB, ur1, ur2, ur3, vect)
Read single Krylov vector from the file.
Definition: arna_io.f:821
subroutine arna_mfop
Write procesor independent variables.
Definition: arna_io.f:132
subroutine arna_rst_read
Read from checkpoints.
Definition: arna_io.f:41
subroutine arna_rst_save
Write restart files.
Definition: arna_io.f:8
subroutine arna_mfosv(ioflds, nout, offs0, stride, strideB, ur1, ur2, ur3, vect)
Write single Krylov vector to the file.
Definition: arna_io.f:770
subroutine arna_read_par(prefix)
Read procesor independent data.
Definition: arna_io.f:203
subroutine io_mbyte_open(hname, ierr)
Open field file.
Definition: io_tools.f:182
subroutine io_mfo_fname(fname, bname, prefix, ierr)
Generate file name according to nek rulles without opening the file.
Definition: io_tools.f:109
subroutine io_mbyte_close(ierr)
Close field file.
Definition: io_tools.f:232
subroutine mntr_logi(mid, priority, logs, ivar)
Write log message adding single integer.
Definition: mntrlog.f:709
subroutine mntr_logr(mid, priority, logs, rvar)
Write log message adding single real.
Definition: mntrlog.f:731
subroutine mntr_warn(mid, logs)
Write warning message.
Definition: mntrlog.f:803
subroutine mntr_abort(mid, logs)
Abort simulation.
Definition: mntrlog.f:837
subroutine mntr_log(mid, priority, logs)
Write log message.
Definition: mntrlog.f:600
subroutine mntr_error(mid, logs)
Write error message.
Definition: mntrlog.f:820
subroutine mntr_check_abort(mid, ierr, logs)
Abort simulation.
Definition: mntrlog.f:856
subroutine mfi_getv(u, v, w, wk, lwk, iskip)
Definition: ic.f:2057
subroutine mfi_gets(u, wk, lwk, iskip)
Definition: ic.f:1923
subroutine mfi_prepare(hname)
Definition: ic.f:2543
subroutine copy(a, b, n)
Definition: math.f:260
subroutine blank(A, N)
Definition: math.f:19
subroutine mfo_outv(u, v, w, nel, mx, my, mz)
Definition: prepost.f:1726
subroutine mfo_outs(u, nel, mx, my, mz)
Definition: prepost.f:1633
subroutine io_init
Definition: prepost.f:1024
subroutine mfo_write_hdr
Definition: prepost.f:1857