ROMS
Loading...
Searching...
No Matches
set_pio_mod Module Reference

Functions/Subroutines

subroutine, public initialize_pio
 
subroutine, public finalize_pio
 
subroutine, public field_iodecomp (ng, iosystem, iotype, iodesc, gtype, ndims, lbk, ubk, lbt, ubt)
 
subroutine, public set_iodecomp
 
subroutine, public state_iodecomp (ng, iosystem, iotype, iodesc, iovname, ndims)
 

Function/Subroutine Documentation

◆ field_iodecomp()

subroutine, public set_pio_mod::field_iodecomp ( integer, intent(in) ng,
type (iosystem_desc_t), intent(in) iosystem,
integer, intent(in) iotype,
type (io_desc_t), intent(out) iodesc,
integer, intent(in) gtype,
integer, intent(in) ndims,
integer, intent(in), optional lbk,
integer, intent(in), optional ubk,
integer, intent(in), optional lbt,
integer, intent(in), optional ubt )

Definition at line 514 of file set_pio.F.

516!
517!***********************************************************************
518! !
519! Sets the IO decomposition descriptor for ROMS field variable types. !
520! !
521! On Input: !
522! !
523! ng Nested grid number (integer) !
524! ioSystem PIO system descriptor (TYPE IOSystem_desc_t) !
525! ioType PIO kind variable type (integer) !
526! gtype Variable C-grid type (integer) !
527! ndims Number of state variable dimensions (integer) !
528! LBk K- or 3rd-dimension Lower bound (integer, OPTIONAL) !
529! UBk K- or 3rd-dimension Upper bound (integer, OPTIONAL) !
530! LBt T- or 4th-dimension Lower bound (integer, OPTIONAL) !
531! UBt T- or 4th-dimension Upper bound (integer, OPTIONAL) !
532! !
533! On Output: !
534! !
535! ioDesc IO decomposition descriptor (TYPE io_desc_t) !
536! !
537!***********************************************************************
538!
539! Imported variable declarations.
540!
541 integer, intent(in) :: ng, ioType, gtype, ndims
542
543 integer, intent(in), optional :: LBk, UBk
544 integer, intent(in), optional :: LBt, UBt
545!
546 TYPE (IOSystem_desc_t), intent(in) :: ioSystem
547 TYPE (io_desc_t), intent(out) :: ioDesc
548!
549! Local variable declarations.
550!
551 logical :: Lboundary
552!
553 integer :: Cgrid, ghost
554 integer :: i, ic, j, jc, k, kc, l, lc, np
555 integer :: Is, Ie, Js, Je
556 integer :: Imin, Imax, Jmin, Jmax
557 integer :: Ioff, Joff, Koff, Loff
558 integer :: Ilen, Isize, Jlen, Jsize, Klen, Ksize, Llen, Lsize
559 integer :: IJlen, IJKlen
560 integer :: my_size
561!
562 integer(PIO_Offset_kind), allocatable :: map_decomp(:)
563!
564!-----------------------------------------------------------------------
565! Set the PIO computational decomposition for ROMS C-type variables
566! and array rank. It is based on variable kind type and its mapping
567! from storage order to memory order.
568!-----------------------------------------------------------------------
569!
570 lboundary=.false.
571
572! Get GLOBAL lower and upper bounds for each variable type in input
573! or ouput NetCDF files.
574!
575 SELECT CASE (gtype)
576 CASE (r2dobc, u2dobc, v2dobc)
577 lboundary=.true.
578 cgrid=2
579 is=0
580 ie=iobounds(ng) % IorJ
581 js=1
582 je=4
583 ioff=1
584 joff=0
585 CASE (r3dobc, u3dobc, v3dobc)
586 lboundary=.true.
587 cgrid=2
588 is=0
589 ie=iobounds(ng) % IorJ
590 js=1
591 je=4
592 ioff=1
593 joff=0
594 CASE (p2dvar, p3dvar)
595 cgrid=1
596 is=iobounds(ng) % ILB_psi
597 ie=iobounds(ng) % IUB_psi
598 js=iobounds(ng) % JLB_psi
599 je=iobounds(ng) % JUB_psi
600 ioff=0
601 joff=1
602 CASE (r2dvar, b3dvar, l3dvar, l4dvar, r3dvar)
603 cgrid=2
604 is=iobounds(ng) % ILB_rho
605 ie=iobounds(ng) % IUB_rho
606 js=iobounds(ng) % JLB_rho
607 je=iobounds(ng) % JUB_rho
608 ioff=1
609 joff=0
610 CASE (u2dvar, u3dvar)
611 cgrid=3
612 is=iobounds(ng) % ILB_u
613 ie=iobounds(ng) % IUB_u
614 js=iobounds(ng) % JLB_u
615 je=iobounds(ng) % JUB_u
616 ioff=0
617 joff=0
618 CASE (v2dvar, v3dvar)
619 cgrid=4
620 is=iobounds(ng) % ILB_v
621 ie=iobounds(ng) % IUB_v
622 js=iobounds(ng) % JLB_v
623 je=iobounds(ng) % JUB_v
624 ioff=1
625 joff=1
626 CASE (w3dvar)
627 cgrid=2
628 is=iobounds(ng) % ILB_rho
629 ie=iobounds(ng) % IUB_rho
630 js=iobounds(ng) % JLB_rho
631 je=iobounds(ng) % JUB_rho
632 ioff=1
633 joff=0
634 END SELECT
635!
636! Get GLOBAL length for each variable dimension.
637!
638 ilen=ie-is+1
639 jlen=je-js+1
640 ijlen=ilen*jlen
641!
642 IF (PRESENT(lbk)) THEN
643 IF (lbk.eq.0) THEN
644 koff=0
645 ELSE
646 koff=1
647 END IF
648 klen=ubk-lbk+1
649 ksize=klen
650 ijklen=ijlen*klen
651 END IF
652!
653 IF (PRESENT(lbt)) THEN
654 IF (lbt.eq.0) THEN
655 loff=0
656 ELSE
657 loff=1
658 END IF
659 llen=ubt-lbt+1
660 lsize=llen
661 END IF
662!
663! Starting/ending I- and J-indices for each decomposition tile
664! according to C-grid locatation, excluding ghost points.
665!
666 IF (lboundary) THEN
667 imin=is
668 imax=ie
669 jmin=js
670 jmax=je
671 ELSE
672 ghost=0
673 imin=bounds(ng) % Imin(cgrid,ghost,myrank)
674 imax=bounds(ng) % Imax(cgrid,ghost,myrank)
675 jmin=bounds(ng) % Jmin(cgrid,ghost,myrank)
676 jmax=bounds(ng) % Jmax(cgrid,ghost,myrank)
677 END IF
678!
679! Allocate 1D array for mapping of the storage order of the variable to
680! its memory order.
681!
682 isize=imax-imin+1
683 jsize=jmax-jmin+1
684!
685 IF (ndims.eq.2) THEN
686 my_size=isize*jsize
687 ELSE IF (ndims.eq.3) THEN
688 my_size=isize*jsize*ksize
689 ELSE IF (ndims.eq.4) THEN
690 my_size=isize*jsize*ksize*lsize
691 END IF
692!
693 IF (.not.ALLOCATED(map_decomp)) THEN
694 allocate ( map_decomp(my_size) )
695 END IF
696 map_decomp=0_pio_offset_kind
697!
698! Set variable decomposition mapping.
699!
700 IF (ndims.eq.2) THEN
701 np=0
702 DO j=jmin,jmax
703 jc=(j-joff)*ilen
704 DO i=imin,imax
705 np=np+1
706 ic=i+ioff+jc
707 map_decomp(np)=ic
708 END DO
709 END DO
710 ELSE IF (ndims.eq.3) THEN
711 np=0
712 DO k=lbk,ubk
713 kc=(k-koff)*ijlen
714 DO j=jmin,jmax
715 jc=(j-joff)*ilen+kc
716 DO i=imin,imax
717 np=np+1
718 ic=i+ioff+jc
719 map_decomp(np)=ic
720 END DO
721 END DO
722 END DO
723 ELSE IF (ndims.eq.4) THEN
724 np=0
725 DO l=lbt,ubt
726 lc=(l-loff)*ijklen
727 DO k=lbk,ubk
728 kc=(k-koff)*ijlen+lc
729 DO j=jmin,jmax
730 jc=(j-joff)*ilen+kc
731 DO i=imin,imax
732 np=np+1
733 ic=i+ioff+jc
734 map_decomp(np)=ic
735 END DO
736 END DO
737 END DO
738 END DO
739 END IF
740!
741! Set IO decomposition descriptor
742!
743 IF (ndims.eq.2) THEN
744 CALL pio_initdecomp (iosystem, iotype, (/ilen,jlen/), &
745 & map_decomp, iodesc)
746 ELSE IF (ndims.eq.3) THEN
747 CALL pio_initdecomp (iosystem, iotype, (/ilen,jlen,klen/), &
748 & map_decomp, iodesc)
749 ELSE IF (ndims.eq.4) THEN
750 CALL pio_initdecomp (iosystem, iotype, (/ilen,jlen,klen,llen/), &
751 & map_decomp, iodesc)
752 END IF
753!
754! Deallocate.
755!
756 IF (allocated(map_decomp)) deallocate (map_decomp)
757!
758 RETURN

References mod_param::b3dvar, mod_param::bounds, mod_param::iobounds, mod_param::l3dvar, mod_param::l4dvar, mod_parallel::myrank, mod_param::p2dvar, mod_param::p3dvar, mod_param::r2dobc, mod_param::r2dvar, mod_param::r3dobc, mod_param::r3dvar, mod_param::u2dobc, mod_param::u2dvar, mod_param::u3dobc, mod_param::u3dvar, mod_param::v2dobc, mod_param::v2dvar, mod_param::v3dobc, mod_param::v3dvar, and mod_param::w3dvar.

Referenced by set_iodecomp().

Here is the caller graph for this function:

◆ finalize_pio()

subroutine, public set_pio_mod::finalize_pio

Definition at line 322 of file set_pio.F.

323!
324!***********************************************************************
325! !
326! Finalizes the PIO subsystem. It frees all the storage memory !
327! associated with the IO decomposition. !
328! !
329!***********************************************************************
330!
331! Local variable declarations.
332!
333 integer :: i, ng, status
334!
335!-----------------------------------------------------------------------
336! Deallocate storage memory associated with IO decomposition.
337!-----------------------------------------------------------------------
338!
339 IF (lpioinitialized) THEN
340!
341! Single precision decomposition descriptors.
342!
343 DO ng=1,ngrids
344 DO i=1,npiocomps
345 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_p2dvar(ng))
346# ifdef ADJUST_BOUNDARY
347 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r2dobc(ng))
348 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u2dobc(ng))
349 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v2dobc(ng))
350# endif
351 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r2dvar(ng))
352 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u2dvar(ng))
353 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v2dvar(ng))
354# if defined SSH_TIDES || defined UV_TIDES
355 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_rtides(ng))
356# endif
357# ifdef SOLVE3D
358# ifdef SEDIMENT
359 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_b3dvar(ng))
360# endif
361# if defined DIAGNOSTICS_BIO && defined ECOSIM
362 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_l3dvar(ng))
363 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_l4dvar(ng))
364# endif
365 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_p3dvar(ng))
366# ifdef ADJUST_BOUNDARY
367 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r3dobc(ng))
368 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u3dobc(ng))
369 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v3dobc(ng))
370# endif
371 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r3dvar(ng))
372 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u3dvar(ng))
373 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v3dvar(ng))
374 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_w3dvar(ng))
375# endif
376 END DO
377 END DO
378!
379! Double precision decomposition descriptors.
380!
381 DO ng=1,ngrids
382 DO i=1,npiocomps
383 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_p2dvar(ng))
384# ifdef ADJUST_BOUNDARY
385 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r2dobc(ng))
386 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u2dobc(ng))
387 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v2dobc(ng))
388# endif
389 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r2dvar(ng))
390 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u2dvar(ng))
391 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v2dvar(ng))
392# if defined SSH_TIDES || defined UV_TIDES
393 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_rtides(ng))
394# endif
395# ifdef SOLVE3D
396# ifdef SEDIMENT
397 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_b3dvar(ng))
398# endif
399# if defined DIAGNOSTICS_BIO && defined ECOSIM
400 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_l3dvar(ng))
401 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_l4dvar(ng))
402# endif
403 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_p3dvar(ng))
404# ifdef ADJUST_BOUNDARY
405 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r3dobc(ng))
406 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u3dobc(ng))
407 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v3dobc(ng))
408# endif
409 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r3dvar(ng))
410 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u3dvar(ng))
411 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v3dvar(ng))
412 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_w3dvar(ng))
413# endif
414 END DO
415 END DO
416!
417! Special restart and harmonics single precision decomposition
418! descriptors.
419!
420 DO ng=1,ngrids
421 DO i=1,npiocomps
422 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_rubar(ng))
423 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_rvbar(ng))
424 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_rzeta(ng))
425 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_ubar(ng))
426 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_vbar(ng))
427 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_zeta(ng))
428# ifdef SOLVE3D
429 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_ruvel(ng))
430 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_rvvel(ng))
431# if defined GLS_MIXING || defined MY25_MIXING
432 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_tkevar(ng))
433# endif
434 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_trcvar(ng))
435 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_uvel(ng))
436 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_vvel(ng))
437# endif
438# if defined AVERAGES && defined AVERAGES_DETIDE && \
439 (defined ssh_tides || defined uv_tides)
440 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r2dhar(ng))
441 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u2dhar(ng))
442 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v2dhar(ng))
443# ifdef SOLVE3D
444 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_r3dhar(ng))
445 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_u3dhar(ng))
446 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_v3dhar(ng))
447# endif
448# endif
449 END DO
450 END DO
451!
452! Special restart and harmonics double precision decomposition
453! descriptors.
454!
455 DO ng=1,ngrids
456 DO i=1,npiocomps
457 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_rubar(ng))
458 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_rvbar(ng))
459 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_rzeta(ng))
460 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_ubar(ng))
461 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_vbar(ng))
462 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_zeta(ng))
463# ifdef SOLVE3D
464 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_ruvel(ng))
465 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_rvvel(ng))
466# if defined GLS_MIXING || defined MY25_MIXING
467 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_tkevar(ng))
468# endif
469 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_trcvar(ng))
470 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_uvel(ng))
471 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_vvel(ng))
472# endif
473# if defined AVERAGES && defined AVERAGES_DETIDE && \
474 (defined ssh_tides || defined uv_tides)
475 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r2dhar(ng))
476 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u2dhar(ng))
477 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v2dhar(ng))
478# ifdef SOLVE3D
479 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_r3dhar(ng))
480 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_u3dhar(ng))
481 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_v3dhar(ng))
482# endif
483# endif
484# if defined PROPAGATOR && defined CHECKPOINTING
485!
486! I/O decomposition descriptors for GST single and double precision
487! state propagator data.
488!
489 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_bvec(ng))
490 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_resid(ng))
491 CALL pio_freedecomp (piosystem(i,ng), iodesc_sp_sworkd(ng))
492!
493 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_bvec(ng))
494 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_resid(ng))
495 CALL pio_freedecomp (piosystem(i,ng), iodesc_dp_sworkd(ng))
496# endif
497 END DO
498 END DO
499!
500!-----------------------------------------------------------------------
501! Shut down and clean up any memory associated with the PIO library.
502!-----------------------------------------------------------------------
503!
504 DO ng=1,ngrids
505 DO i=1,npiocomps
506 CALL pio_finalize (piosystem(i,ng), status)
507 END DO
508 END DO
509 END IF
510!
511 RETURN

References mod_pio_netcdf::iodesc_dp_b3dvar, mod_pio_netcdf::iodesc_dp_bvec, mod_pio_netcdf::iodesc_dp_l3dvar, mod_pio_netcdf::iodesc_dp_l4dvar, mod_pio_netcdf::iodesc_dp_p2dvar, mod_pio_netcdf::iodesc_dp_p3dvar, mod_pio_netcdf::iodesc_dp_r2dhar, mod_pio_netcdf::iodesc_dp_r2dobc, mod_pio_netcdf::iodesc_dp_r2dvar, mod_pio_netcdf::iodesc_dp_r3dhar, mod_pio_netcdf::iodesc_dp_r3dobc, mod_pio_netcdf::iodesc_dp_r3dvar, mod_pio_netcdf::iodesc_dp_resid, mod_pio_netcdf::iodesc_dp_rtides, mod_pio_netcdf::iodesc_dp_rubar, mod_pio_netcdf::iodesc_dp_ruvel, mod_pio_netcdf::iodesc_dp_rvbar, mod_pio_netcdf::iodesc_dp_rvvel, mod_pio_netcdf::iodesc_dp_rzeta, mod_pio_netcdf::iodesc_dp_sworkd, mod_pio_netcdf::iodesc_dp_tkevar, mod_pio_netcdf::iodesc_dp_trcvar, mod_pio_netcdf::iodesc_dp_u2dhar, mod_pio_netcdf::iodesc_dp_u2dobc, mod_pio_netcdf::iodesc_dp_u2dvar, mod_pio_netcdf::iodesc_dp_u3dhar, mod_pio_netcdf::iodesc_dp_u3dobc, mod_pio_netcdf::iodesc_dp_u3dvar, mod_pio_netcdf::iodesc_dp_ubar, mod_pio_netcdf::iodesc_dp_uvel, mod_pio_netcdf::iodesc_dp_v2dhar, mod_pio_netcdf::iodesc_dp_v2dobc, mod_pio_netcdf::iodesc_dp_v2dvar, mod_pio_netcdf::iodesc_dp_v3dhar, mod_pio_netcdf::iodesc_dp_v3dobc, mod_pio_netcdf::iodesc_dp_v3dvar, mod_pio_netcdf::iodesc_dp_vbar, mod_pio_netcdf::iodesc_dp_vvel, mod_pio_netcdf::iodesc_dp_w3dvar, mod_pio_netcdf::iodesc_dp_zeta, mod_pio_netcdf::iodesc_sp_b3dvar, mod_pio_netcdf::iodesc_sp_bvec, mod_pio_netcdf::iodesc_sp_l3dvar, mod_pio_netcdf::iodesc_sp_l4dvar, mod_pio_netcdf::iodesc_sp_p2dvar, mod_pio_netcdf::iodesc_sp_p3dvar, mod_pio_netcdf::iodesc_sp_r2dhar, mod_pio_netcdf::iodesc_sp_r2dobc, mod_pio_netcdf::iodesc_sp_r2dvar, mod_pio_netcdf::iodesc_sp_r3dhar, mod_pio_netcdf::iodesc_sp_r3dobc, mod_pio_netcdf::iodesc_sp_r3dvar, mod_pio_netcdf::iodesc_sp_resid, mod_pio_netcdf::iodesc_sp_rtides, mod_pio_netcdf::iodesc_sp_rubar, mod_pio_netcdf::iodesc_sp_ruvel, mod_pio_netcdf::iodesc_sp_rvbar, mod_pio_netcdf::iodesc_sp_rvvel, mod_pio_netcdf::iodesc_sp_rzeta, mod_pio_netcdf::iodesc_sp_sworkd, mod_pio_netcdf::iodesc_sp_tkevar, mod_pio_netcdf::iodesc_sp_trcvar, mod_pio_netcdf::iodesc_sp_u2dhar, mod_pio_netcdf::iodesc_sp_u2dobc, mod_pio_netcdf::iodesc_sp_u2dvar, mod_pio_netcdf::iodesc_sp_u3dhar, mod_pio_netcdf::iodesc_sp_u3dobc, mod_pio_netcdf::iodesc_sp_u3dvar, mod_pio_netcdf::iodesc_sp_ubar, mod_pio_netcdf::iodesc_sp_uvel, mod_pio_netcdf::iodesc_sp_v2dhar, mod_pio_netcdf::iodesc_sp_v2dobc, mod_pio_netcdf::iodesc_sp_v2dvar, mod_pio_netcdf::iodesc_sp_v3dhar, mod_pio_netcdf::iodesc_sp_v3dobc, mod_pio_netcdf::iodesc_sp_v3dvar, mod_pio_netcdf::iodesc_sp_vbar, mod_pio_netcdf::iodesc_sp_vvel, mod_pio_netcdf::iodesc_sp_w3dvar, mod_pio_netcdf::iodesc_sp_zeta, mod_pio_netcdf::lpioinitialized, mod_param::ngrids, mod_pio_netcdf::npiocomps, and mod_pio_netcdf::piosystem.

Referenced by mct_driver(), and myroms().

Here is the caller graph for this function:

◆ initialize_pio()

subroutine, public set_pio_mod::initialize_pio

Definition at line 49 of file set_pio.F.

50!
51!***********************************************************************
52! !
53! Initializes the PIO subsystem. It sets PIO decomposition for all !
54! ROMS variables. !
55! !
56!***********************************************************************
57!
58! Local variable declarations.
59!
60# ifdef ASYNCHRONOUS_PIO
61 logical, allocatable :: Lranks(:)
62!
63 integer :: ComputeSize
64
65 integer, allocatable :: COMPUTE_COMM(:,:), IO_COMM(:)
66 integer, allocatable :: Compute_Ranks(:,:), IO_Ranks(:)
67# endif
68 integer :: MyError
69 integer :: i, ic, ng
70!
71 character (len=*), parameter :: MyFile = &
72 & __FILE__//", initialize_pio"
73!
74!-----------------------------------------------------------------------
75! Initialize PIO and get IO system descriptor. It uses collective
76! communicatios.
77!-----------------------------------------------------------------------
78!
79 IF (.not.allocated(piosystem)) THEN
80 allocate ( piosystem(npiocomps,ngrids) )
81 END IF
82!
83! Set PIO internal level of debug information. The default value is 0,
84! allowed values 0-6.
85!
86 IF (pio_debug.gt.0) THEN
87 CALL pio_setdebuglevel (pio_debug)
88 END IF
89
90# if defined ASYNCHRONOUS_PIO
91!
92!-----------------------------------------------------------------------
93! If NCAR/UNIDATA PIO library, set the ranks of the computational and
94! IO processes with respect the initial (peer) communicator. Notice
95! that the communicator is natively split inside "PIO_init". Therefore,
96! the I/O processes do not return from the call. Instead go to an
97! internal loop and wait to receive further instructions from the
98! computational processes. I think that this is a better strategy.
99!-----------------------------------------------------------------------
100!
101! Set peer communicator as the initial ROMS communicator.
102!
103 peer_comm_world=ocn_comm_world
104 peersize=numthreads
105 peerrank=myrank
106 computesize=peersize-pio_numiotasks
107!
108! Allocate and initialize local arrays.
109!
110 IF (.not.allocated(compute_comm)) THEN
111 allocate ( compute_comm(npiocomps,ngrids) )
112 compute_comm=mpi_comm_null
113 END IF
114 IF (.not.allocated(io_comm)) THEN
115 allocate ( io_comm(ngrids) )
116 io_comm=mpi_comm_null
117 END IF
118!
119 IF (.not.allocated(lranks)) THEN
120 allocate ( lranks(0:peersize-1) )
121 lranks(0:peersize-1)=.true.
122 END IF
123 IF (.not.allocated(compute_ranks)) THEN
124 allocate ( compute_ranks(computesize,npiocomps) )
125 compute_ranks=-1
126 END IF
127 IF (.not.allocated(io_ranks)) THEN
128 allocate ( io_ranks(pio_numiotasks) )
129 io_ranks=-1
130 END IF
131!
132! Set the ranks of the dedicated I/O processes with respect the peer
133! communicator.
134!
135 ic=pio_base
136 io_ranks(1)=ic
137 lranks(ic)=.false.
138 DO i=2,pio_numiotasks
139 IF ((ic+pio_stride).le.(peersize-1)) THEN
140 ic=ic+pio_stride
141 io_ranks(i)=ic
142 lranks(ic)=.false.
143 END IF
144 END DO
145 WRITE (cioranks,'(*(i0,1x))') io_ranks
146!
147! Set the ranks of the computational processes with respect the peer
148! communicator.
149!
150 ic=0
151 DO i=0,peersize-1
152 IF (lranks(i)) THEN
153 ic=ic+1
154 compute_ranks(ic,ipioroms)=i
155 END IF
156 END DO
157 WRITE (ccompranks,'(*(i0,1x))') compute_ranks
158!
159! Create a new IO system for asynchronous or synchronous I/O. The
160! asynchronous I/O is only possible PIO type ("io_pio") files.
161!
162!! IF ((inp_lib.eq.io_pio).and.(out_lib.eq.io_pio)) THEN
163 IF (out_lib.eq.io_pio) THEN
164 DO ng=1,ngrids
165 CALL pio_init (piosystem(ipioroms:,ng), &
166 & peer_comm_world, &
167 & (/computesize/), &
168 & compute_ranks, &
169 & io_ranks, &
170 & pio_rearranger, &
171 & compute_comm(ipioroms:,ng), &
172 & io_comm(ng))
173 END DO
174!
175! Initialize ROMS kernel communicators.
176!
177 ng=1
178 ocn_comm_world=compute_comm(ipioroms,ng)
179 io_comm_world =io_comm(ng)
180!
181! Reset ROMS communicator parameters.
182!
183 CALL mpi_comm_size (ocn_comm_world, numthreads, myerror)
184 CALL mpi_comm_rank (ocn_comm_world, myrank, myerror)
185!
186 master=myrank.eq.mymaster
187# ifdef PARALLEL_IO
188 inpthread=.true.
189 outthread=.true.
190# else
191 IF (myrank.eq.0) THEN
192 inpthread=.true.
193 outthread=.true.
194 ELSE
195 inpthread=.false.
196 outthread=.false.
197 END IF
198# endif
199!
200! Deallocate local arrays.
201!
202 IF (allocated(compute_comm)) deallocate (compute_comm)
203 IF (allocated(io_comm)) deallocate (io_comm)
204 IF (allocated(lranks)) deallocate (lranks)
205 IF (allocated(compute_ranks)) deallocate (compute_ranks)
206 IF (allocated(io_ranks)) deallocate (io_ranks)
207!
208! Otherwise, do synchronous I/O.
209!
210 ELSE
211 DO ng=1,ngrids
212 CALL pio_init (myrank, &
213 & ocn_comm_world, &
214 & pio_numiotasks, &
215 & pio_aggregator, &
216 & pio_stride, &
217 & pio_rearranger, &
218 & piosystem(ipioroms,ng), &
219 & base = pio_base)
220 END DO
221 END IF
222
223# elif defined ASYNCHRONOUS_SCORPIO
224!
225!-----------------------------------------------------------------------
226! If SCORPIO library, set the ranks of the computational and I/O
227! IO processes with respect the initial (peer) communicator. Unlike
228! the NCAR/UNIDATA version, there is not a version to split the
229! communicator internally in the call to "PIO_init". We need to
230! split the communicator previously by calling "set_pio_async".
231! (HGA: this option does not work yet).
232!-----------------------------------------------------------------------
233!
234 DO ng=1,ngrids
235!! IF ((inp_lib.eq.io_pio).and.(out_lib.eq.io_pio)) THEN
236 IF (out_lib.eq.io_pio) THEN
237 CALL pio_init (piosystem(ipioroms:,ng), &
238 & peer_comm_world, &
239 & (/ocn_comm_world/), &
240 & io_comm_world, &
241 & pio_rearranger)
242 ELSE
243 CALL pio_init (myrank, &
244 & ocn_comm_world, &
245 & pio_numiotasks, &
246 & pio_aggregator, &
247 & pio_stride, &
248 & pio_rearranger, &
249 & piosystem(ipioroms,ng), &
250 & base = pio_base)
251 END IF
252 END DO
253
254# else
255!
256!-----------------------------------------------------------------------
257! Initialize synchronous PIO system.
258!-----------------------------------------------------------------------
259!
260 DO ng=1,ngrids
261 CALL pio_init (myrank, &
262 & ocn_comm_world, &
263 & pio_numiotasks, &
264 & pio_aggregator, &
265 & pio_stride, &
266 & pio_rearranger, &
267 & piosystem(ipioroms,ng), &
268 & base = pio_base)
269 END DO
270# endif
271!
272!-----------------------------------------------------------------------
273! Set PIO rearrangement communication options.
274!-----------------------------------------------------------------------
275!
276 lpioinitialized=.true.
277!
278! The rearranger communication type "pio_rearr_comm" has two choices:
279!
280! PIO_rearr_comm_p2p Point to point (send/recive)
281! PIO_rearr_comm_coll Collective (gather/scatter)
282!
283! The rearranger communication flow control direction "pio_rearr_fcd"
284! has four choices:
285!
286! PIO_rearr_comm_fc_2d_enable COMM to IO processes and viceversa
287! PIO_rearr_comm_fc_1d_comp2io COMM to IO processes only
288! PIO_rearr_comm_fc_1d_io2comp IO to COMM processes only
289! PIO_rearr_comm_fc_2d_disable Disable flow control
290!
291! Compute to IO (C2I) processes:
292!
293! pio_rearr_C2I_HS Enable handshake (true/false)
294! pio_rearr_C2I_iS Enable Isends (true/false)
295! pio_rearr_C2I_PR Maximum pending requests
296!
297! IO to compute (I2C) processes:
298!
299! pio_rearr_I2C_HS Enable handshake (true/false)
300! pio_rearr_I2C_iS Enable Isends (true/false)
301! pio_rearr_I2C_PR Maximum pending requests
302!
303! Use PIO_REARR_COMM_UNLIMITED_PEND_REQ for unlimited number of
304! requests.
305!
306 DO ng=1,ngrids
307 myerror=pio_set_rearr_opts(piosystem(ipioroms,ng), &
308 pio_rearr_comm, &
309 & pio_rearr_fcd, &
310 & pio_rearr_c2i_hs, &
311 & pio_rearr_c2i_is, &
312 & pio_rearr_c2i_pr, &
313 & pio_rearr_i2c_hs, &
314 & pio_rearr_i2c_is, &
315 & pio_rearr_i2c_pr)
316 IF (founderror(myerror, pio_noerr, __line__, myfile)) RETURN
317 END DO
318!
319 RETURN

References mod_pio_netcdf::ccompranks, mod_pio_netcdf::cioranks, strings_mod::founderror(), mod_parallel::inpthread, mod_pio_netcdf::ipioroms, mod_pio_netcdf::lpioinitialized, mod_parallel::master, mod_parallel::mymaster, mod_parallel::myrank, mod_param::ngrids, mod_pio_netcdf::npiocomps, mod_parallel::numthreads, mod_parallel::ocn_comm_world, mod_parallel::outthread, mod_pio_netcdf::pio_aggregator, mod_pio_netcdf::pio_base, mod_pio_netcdf::pio_debug, mod_pio_netcdf::pio_numiotasks, mod_pio_netcdf::pio_rearr_c2i_hs, mod_pio_netcdf::pio_rearr_c2i_is, mod_pio_netcdf::pio_rearr_c2i_pr, mod_pio_netcdf::pio_rearr_comm, mod_pio_netcdf::pio_rearr_fcd, mod_pio_netcdf::pio_rearr_i2c_hs, mod_pio_netcdf::pio_rearr_i2c_is, mod_pio_netcdf::pio_rearr_i2c_pr, mod_pio_netcdf::pio_rearranger, mod_pio_netcdf::pio_stride, and mod_pio_netcdf::piosystem.

Here is the call graph for this function:

◆ set_iodecomp()

subroutine, public set_pio_mod::set_iodecomp

Definition at line 761 of file set_pio.F.

762!
763!***********************************************************************
764! !
765! Sets the IO decomposition descriptors for ROMS input and output !
766! variables. They are used for the mapping between computational !
767! and I/O processes. !
768! !
769!***********************************************************************
770!
771! Local variable declarations.
772!
773 integer :: ng
774!
775!-----------------------------------------------------------------------
776! Allocate I/O decomposition descriptors.
777!-----------------------------------------------------------------------
778!
779! I/O decomposition descriptors for single precision data.
780!
781 allocate ( iodesc_sp_p2dvar(ngrids) )
782# ifdef ADJUST_WSTRESS
783 allocate ( iodesc_sp_u2dfrc(ngrids) )
784 allocate ( iodesc_sp_v2dfrc(ngrids) )
785# endif
786# ifdef ADJUST_BOUNDARY
787 allocate ( iodesc_sp_r2dobc(ngrids) )
788 allocate ( iodesc_sp_u2dobc(ngrids) )
789 allocate ( iodesc_sp_v2dobc(ngrids) )
790# endif
791 allocate ( iodesc_sp_r2dvar(ngrids) )
792 allocate ( iodesc_sp_u2dvar(ngrids) )
793 allocate ( iodesc_sp_v2dvar(ngrids) )
794# if defined SSH_TIDES || defined UV_TIDES
795 allocate ( iodesc_sp_rtides(ngrids) )
796# endif
797# ifdef SOLVE3D
798# ifdef SEDIMENT
799 allocate ( iodesc_sp_b3dvar(ngrids) )
800# endif
801# if defined DIAGNOSTICS_BIO && defined ECOSIM
802 allocate ( iodesc_sp_l3dvar(ngrids) )
803 allocate ( iodesc_sp_l4dvar(ngrids) )
804# endif
805 allocate ( iodesc_sp_p3dvar(ngrids) )
806# ifdef ADJUST_STFLUX
807 allocate ( iodesc_sp_r2dfrc(ngrids) )
808# endif
809# ifdef ADJUST_BOUNDARY
810 allocate ( iodesc_sp_r3dobc(ngrids) )
811 allocate ( iodesc_sp_u3dobc(ngrids) )
812 allocate ( iodesc_sp_v3dobc(ngrids) )
813# endif
814 allocate ( iodesc_sp_r3dvar(ngrids) )
815 allocate ( iodesc_sp_u3dvar(ngrids) )
816 allocate ( iodesc_sp_v3dvar(ngrids) )
817 allocate ( iodesc_sp_w3dvar(ngrids) )
818# endif
819!
820! I/O decomposition descriptors for double precision data.
821!
822 allocate ( iodesc_dp_p2dvar(ngrids) )
823# ifdef ADJUST_WSTRESS
824 allocate ( iodesc_dp_u2dfrc(ngrids) )
825 allocate ( iodesc_dp_v2dfrc(ngrids) )
826# endif
827# ifdef ADJUST_BOUNDARY
828 allocate ( iodesc_dp_r2dobc(ngrids) )
829 allocate ( iodesc_dp_u2dobc(ngrids) )
830 allocate ( iodesc_dp_v2dobc(ngrids) )
831# endif
832 allocate ( iodesc_dp_r2dvar(ngrids) )
833 allocate ( iodesc_dp_u2dvar(ngrids) )
834 allocate ( iodesc_dp_v2dvar(ngrids) )
835# if defined SSH_TIDES || defined UV_TIDES
836 allocate ( iodesc_dp_rtides(ngrids) )
837# endif
838# ifdef SOLVE3D
839# ifdef SEDIMENT
840 allocate ( iodesc_dp_b3dvar(ngrids) )
841# endif
842# if defined DIAGNOSTICS_BIO && defined ECOSIM
843 allocate ( iodesc_dp_l3dvar(ngrids) )
844 allocate ( iodesc_dp_l4dvar(ngrids) )
845# endif
846 allocate ( iodesc_dp_p3dvar(ngrids) )
847# ifdef ADJUST_STFLUX
848 allocate ( iodesc_dp_r2dfrc(ngrids) )
849# endif
850# ifdef ADJUST_BOUNDARY
851 allocate ( iodesc_dp_r3dobc(ngrids) )
852 allocate ( iodesc_dp_u3dobc(ngrids) )
853 allocate ( iodesc_dp_v3dobc(ngrids) )
854# endif
855 allocate ( iodesc_dp_r3dvar(ngrids) )
856 allocate ( iodesc_dp_u3dvar(ngrids) )
857 allocate ( iodesc_dp_v3dvar(ngrids) )
858 allocate ( iodesc_dp_w3dvar(ngrids) )
859# endif
860!
861! I/O decomposition descriptors for special single precision
862! restart and harmonics data.
863!
864 allocate ( iodesc_sp_rubar(ngrids) )
865 allocate ( iodesc_sp_rvbar(ngrids) )
866 allocate ( iodesc_sp_rzeta(ngrids) )
867 allocate ( iodesc_sp_ubar(ngrids) )
868 allocate ( iodesc_sp_vbar(ngrids) )
869 allocate ( iodesc_sp_zeta(ngrids) )
870# ifdef SOLVE3D
871 allocate ( iodesc_sp_ruvel(ngrids) )
872 allocate ( iodesc_sp_rvvel(ngrids) )
873# if defined GLS_MIXING || defined MY25_MIXING
874 allocate ( iodesc_sp_tkevar(ngrids) )
875# endif
876 allocate ( iodesc_sp_trcvar(ngrids) )
877 allocate ( iodesc_sp_uvel(ngrids) )
878 allocate ( iodesc_sp_vvel(ngrids) )
879# endif
880# if defined AVERAGES && defined AVERAGES_DETIDE && \
881 (defined ssh_tides || defined uv_tides)
882!
883 allocate ( iodesc_sp_r2dvar(ngrids) )
884 allocate ( iodesc_sp_u2dvar(ngrids) )
885 allocate ( iodesc_sp_v2dvar(ngrids) )
886# ifdef SOLVE3D
887 allocate ( iodesc_sp_r3dvar(ngrids) )
888 allocate ( iodesc_sp_u3dvar(ngrids) )
889 allocate ( iodesc_sp_v3dvar(ngrids) )
890# endif
891# endif
892!
893! I/O decomposition descriptors for special double precison
894! restart and harmonics data.
895!
896 allocate ( iodesc_dp_rubar(ngrids) )
897 allocate ( iodesc_dp_rvbar(ngrids) )
898 allocate ( iodesc_dp_rzeta(ngrids) )
899 allocate ( iodesc_dp_ubar(ngrids) )
900 allocate ( iodesc_dp_vbar(ngrids) )
901 allocate ( iodesc_dp_zeta(ngrids) )
902# ifdef SOLVE3D
903 allocate ( iodesc_dp_ruvel(ngrids) )
904 allocate ( iodesc_dp_rvvel(ngrids) )
905# if defined GLS_MIXING || defined MY25_MIXING
906 allocate ( iodesc_dp_tkevar(ngrids) )
907# endif
908 allocate ( iodesc_dp_trcvar(ngrids) )
909 allocate ( iodesc_dp_uvel(ngrids) )
910 allocate ( iodesc_dp_vvel(ngrids) )
911# endif
912# if defined AVERAGES && defined AVERAGES_DETIDE && \
913 (defined ssh_tides || defined uv_tides)
914!
915 allocate ( iodesc_dp_r2dvar(ngrids) )
916 allocate ( iodesc_dp_u2dvar(ngrids) )
917 allocate ( iodesc_dp_v2dvar(ngrids) )
918# ifdef SOLVE3D
919 allocate ( iodesc_dp_r3dvar(ngrids) )
920 allocate ( iodesc_dp_u3dvar(ngrids) )
921 allocate ( iodesc_dp_v3dvar(ngrids) )
922# endif
923# endif
924# if defined PROPAGATOR && defined CHECKPOINTING
925!
926! I/O decomposition descriptors for GST single and double precision
927! state propagator data. Its values are set in routine "wpoints_tile".
928!
929 allocate ( iodesc_sp_bvec(ngrids) )
930 allocate ( iodesc_sp_resid(ngrids) )
931 allocate ( iodesc_sp_sworkd(ngrids) )
932!
933 allocate ( iodesc_dp_bvec(ngrids) )
934 allocate ( iodesc_dp_resid(ngrids) )
935 allocate ( iodesc_dp_sworkd(ngrids) )
936# endif
937!
938!-----------------------------------------------------------------------
939! Set the PIO computational decomposition for ROMS C-type variables
940! and array rank. It is based on variable kind type and its mapping
941! from storage order to memory order.
942!-----------------------------------------------------------------------
943!
944! Set I/O decomposition descriptors for single precision data
945!
946 DO ng=1,ngrids
947 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
948 & iodesc_sp_p2dvar(ng), &
949 & p2dvar, 2)
950 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
951 & iodesc_sp_r2dvar(ng), &
952 & r2dvar, 2)
953 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
954 & iodesc_sp_u2dvar(ng), &
955 & u2dvar, 2)
956 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
957 & iodesc_sp_v2dvar(ng), &
958 & v2dvar, 2)
959# if defined SSH_TIDES || defined UV_TIDES
960 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
961 & iodesc_sp_rtides(ng), &
962 & r2dvar+4, 3, 1, ntc(ng))
963# endif
964# ifdef SOLVE3D
965# ifdef SEDIMENT
966 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
967 & iodesc_sp_b3dvar(ng), &
968 & b3dvar, 3, 1, nbed)
969# endif
970# if defined DIAGNOSTICS_BIO && defined ECOSIM
971 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
972 & iodesc_sp_l3dvar(ng), &
973 & l3dvar, 3, 1, ndbands)
974 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
975 & iodesc_sp_l4dvar(ng), &
976 & l4dvar, 4, 1, n(ng), ndbands)
977# endif
978 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
979 & iodesc_sp_p3dvar(ng), &
980 & p3dvar, 3, 1, n(ng))
981 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
982 & iodesc_sp_r3dvar(ng), &
983 & r3dvar, 3, 1, n(ng))
984 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
985 & iodesc_sp_u3dvar(ng), &
986 & u3dvar, 3, 1, n(ng))
987 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
988 & iodesc_sp_v3dvar(ng), &
989 & v3dvar, 3, 1, n(ng))
990 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
991 & iodesc_sp_w3dvar(ng), &
992 & w3dvar, 3, 0, n(ng))
993# endif
994# if defined ADJUST_STFLUX && defined DISTRIBUTE
995 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
996 & iodesc_sp_r2dfrc(ng), &
997 & r2dvar, 3, 1, nfrec(ng))
998# endif
999# ifdef ADJUST_WSTRESS
1000 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1001 & iodesc_sp_u2dfrc(ng), &
1002 & u2dvar, 3, 1, nfrec(ng))
1003 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1004 & iodesc_sp_v2dfrc(ng), &
1005 & v2dvar, 3, 1, nfrec(ng))
1006# endif
1007# ifdef ADJUST_BOUNDARY
1008 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1009 & iodesc_sp_r2dobc(ng), &
1010 & r2dobc, 3, 1, nbrec(ng))
1011 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1012 & iodesc_sp_u2dobc(ng), &
1013 & u2dobc, 3, 1, nbrec(ng))
1014 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1015 & iodesc_sp_v2dobc(ng), &
1016 & v2dobc, 3, 1, nbrec(ng))
1017# ifdef SOLVE3D
1018 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1019 & iodesc_sp_r3dobc(ng), &
1020 & r3dobc, 4, 1, n(ng), 1, nbrec(ng))
1021 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1022 & iodesc_sp_u3dobc(ng), &
1023 & u3dobc, 4, 1, n(ng), 1, nbrec(ng))
1024 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1025 & iodesc_sp_v3dobc(ng), &
1026 & v3dobc, 4, 1, n(ng), 1, nbrec(ng))
1027# endif
1028# endif
1029 END DO
1030!
1031! Set IO decomposition descriptors for double precision data.
1032!
1033 DO ng=1,ngrids
1034 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1035 & iodesc_dp_p2dvar(ng), &
1036 & p2dvar, 2)
1037 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1038 & iodesc_dp_r2dvar(ng), &
1039 & r2dvar, 2)
1040 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1041 & iodesc_dp_u2dvar(ng), &
1042 & u2dvar, 2)
1043 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1044 & iodesc_dp_v2dvar(ng), &
1045 & v2dvar, 2)
1046# if defined SSH_TIDES || defined UV_TIDES
1047 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1048 & iodesc_dp_rtides(ng), &
1049 & r2dvar+4, 3, 1, ntc(ng))
1050# endif
1051# ifdef SOLVE3D
1052# ifdef SEDIMENT
1053 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1054 & iodesc_dp_b3dvar(ng), &
1055 & b3dvar, 3, 1, nbed)
1056# endif
1057# if defined DIAGNOSTICS_BIO && defined ECOSIM
1058 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1059 & iodesc_dp_l3dvar(ng), &
1060 & l3dvar, 3, 1, ndbands)
1061 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1062 & iodesc_dp_l4dvar(ng), &
1063 & l4dvar, 4, 1, n(ng), ndbands)
1064# endif
1065 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1066 & iodesc_dp_p3dvar(ng), &
1067 & p3dvar, 3, 1, n(ng))
1068 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1069 & iodesc_dp_r3dvar(ng), &
1070 & r3dvar, 3, 1, n(ng))
1071 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1072 & iodesc_dp_u3dvar(ng), &
1073 & u3dvar, 3, 1, n(ng))
1074 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1075 & iodesc_dp_v3dvar(ng), &
1076 & v3dvar, 3, 1, n(ng))
1077 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1078 & iodesc_dp_w3dvar(ng), &
1079 & w3dvar, 3, 0, n(ng))
1080# endif
1081# if defined ADJUST_STFLUX && defined DISTRIBUTE
1082 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1083 & iodesc_dp_r2dfrc(ng), &
1084 & r2dvar, 3, 1, nfrec(ng))
1085# endif
1086# ifdef ADJUST_WSTRESS
1087 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1088 & iodesc_dp_u2dfrc(ng), &
1089 & u2dvar, 3, 1, nfrec(ng))
1090 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1091 & iodesc_dp_v2dfrc(ng), &
1092 & v2dvar, 3, 1, nfrec(ng))
1093# endif
1094# ifdef ADJUST_BOUNDARY
1095 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1096 & iodesc_dp_r2dobc(ng), &
1097 & r2dobc, 3, 1, nbrec(ng))
1098 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1099 & iodesc_dp_u2dobc(ng), &
1100 & u2dobc, 3, 1, nbrec(ng))
1101 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1102 & iodesc_dp_v2dobc(ng), &
1103 & v2dobc, 3, 1, nbrec(ng))
1104# ifdef SOLVE3D
1105 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1106 & iodesc_dp_r3dobc(ng), &
1107 & r3dobc, 4, 1, n(ng), 1, nbrec(ng))
1108 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1109 & iodesc_dp_u3dobc(ng), &
1110 & u3dobc, 4, 1, n(ng), 1, nbrec(ng))
1111 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1112 & iodesc_dp_v3dobc(ng), &
1113 & v3dobc, 4, 1, n(ng), 1, nbrec(ng))
1114# endif
1115# endif
1116 END DO
1117!
1118! Set I/O decomposition descriptors for special single precision
1119! restart and harmonics data.
1120!
1121 DO ng=1,ngrids
1122 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1123 & iodesc_sp_rubar(ng), &
1124 & u2dvar, 3, 1, 2)
1125 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1126 & iodesc_sp_rvbar(ng), &
1127 & v2dvar, 3, 1, 2)
1128 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1129 & iodesc_sp_rzeta(ng), &
1130 & r2dvar, 3, 1, 2)
1131 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1132 & iodesc_sp_ubar(ng), &
1133 & u2dvar, 3, 1, 3)
1134 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1135 & iodesc_sp_vbar(ng), &
1136 & v2dvar, 3, 1, 3)
1137 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1138 & iodesc_sp_zeta(ng), &
1139 & r2dvar, 3, 1, 3)
1140# ifdef SOLVE3D
1141 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1142 & iodesc_sp_ruvel(ng), &
1143 & u3dvar, 4, 0, n(ng), 1, 2)
1144 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1145 & iodesc_sp_rvvel(ng), &
1146 & v3dvar, 4, 0, n(ng), 1, 2)
1147# if defined GLS_MIXING || defined MY25_MIXING
1148 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1149 & iodesc_sp_tkevar(ng), &
1150 & r3dvar, 4, 0, n(ng), 1, 2)
1151# endif
1152 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1153 & iodesc_sp_trcvar(ng), &
1154 & r3dvar, 4, 1, n(ng), 1, 2)
1155 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1156 & iodesc_sp_uvel(ng), &
1157 & u3dvar, 4, 1, n(ng), 1, 2)
1158 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1159 & iodesc_sp_vvel(ng), &
1160 & v3dvar, 4, 1, n(ng), 1, 2)
1161# endif
1162
1163# if defined AVERAGES && defined AVERAGES_DETIDE && \
1164 (defined ssh_tides || defined uv_tides)
1165 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1166 & iodesc_sp_r2dhar(ng), &
1167 & r2dvar, 3, 0, 2*ntc(ng))
1168 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1169 & iodesc_sp_u2dhar(ng), &
1170 & u2dvar, 3, 0, 2*ntc(ng))
1171 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1172 & iodesc_sp_v2dhar(ng), &
1173 & v2dvar, 3, 0, 2*ntc(ng))
1174# ifdef SOLVE3D
1175 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1176 & iodesc_sp_r3dhar(ng), &
1177 & r3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1178 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1179 & iodesc_sp_u3dhar(ng), &
1180 & u3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1181 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_real, &
1182 & iodesc_sp_v3dhar(ng), &
1183 & v3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1184# endif
1185# endif
1186 END DO
1187!
1188! Set I/O decomposition descriptors for special double precision
1189! restart and harmonics data.
1190!
1191 DO ng=1,ngrids
1192 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1193 & iodesc_dp_rubar(ng), &
1194 & u2dvar, 3, 1, 2)
1195 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1196 & iodesc_dp_rvbar(ng), &
1197 & v2dvar, 3, 1, 2)
1198 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1199 & iodesc_dp_rzeta(ng), &
1200 & r2dvar, 3, 1, 2)
1201 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1202 & iodesc_dp_ubar(ng), &
1203 & u2dvar, 3, 1, 3)
1204 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1205 & iodesc_dp_vbar(ng), &
1206 & v2dvar, 3, 1, 3)
1207 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1208 & iodesc_dp_zeta(ng), &
1209 & r2dvar, 3, 1, 3)
1210# ifdef SOLVE3D
1211 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1212 & iodesc_dp_ruvel(ng), &
1213 & u3dvar, 4, 0, n(ng), 1, 2)
1214 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1215 & iodesc_dp_rvvel(ng), &
1216 & v3dvar, 4, 0, n(ng), 1, 2)
1217# if defined GLS_MIXING || defined MY25_MIXING
1218 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1219 & iodesc_dp_tkevar(ng), &
1220 & r3dvar, 4, 0, n(ng), 1, 2)
1221# endif
1222 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1223 & iodesc_dp_trcvar(ng), &
1224 & r3dvar, 4, 1, n(ng), 1, 2)
1225 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1226 & iodesc_dp_uvel(ng), &
1227 & u3dvar, 4, 1, n(ng), 1, 2)
1228 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1229 & iodesc_dp_vvel(ng), &
1230 & v3dvar, 4, 1, n(ng), 1, 2)
1231# endif
1232
1233# if defined AVERAGES && defined AVERAGES_DETIDE && \
1234 (defined ssh_tides || defined uv_tides)
1235 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1236 & iodesc_dp_r2dhar(ng), &
1237 & r2dvar, 3, 0, 2*ntc(ng))
1238 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1239 & iodesc_dp_u2dhar(ng), &
1240 & u2dvar, 3, 0, 2*ntc(ng))
1241 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1242 & iodesc_dp_v2dhar(ng), &
1243 & v2dvar, 3, 0, 2*ntc(ng))
1244# ifdef SOLVE3D
1245 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1246 & iodesc_dp_r3dhar(ng), &
1247 & r3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1248 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1249 & iodesc_dp_u3dhar(ng), &
1250 & u3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1251 CALL field_iodecomp (ng, piosystem(ipioroms,ng), pio_double, &
1252 & iodesc_dp_v3dhar(ng), &
1253 & v3dvar, 4, 1, n(ng), 0, 2*ntc(ng))
1254# endif
1255# endif
1256 END DO
1257!
1258 RETURN

References mod_param::b3dvar, mod_pio_netcdf::ccompranks, mod_pio_netcdf::cioranks, field_iodecomp(), strings_mod::founderror(), mod_parallel::inpthread, mod_pio_netcdf::iodesc_dp_b3dvar, mod_pio_netcdf::iodesc_dp_bvec, mod_pio_netcdf::iodesc_dp_l3dvar, mod_pio_netcdf::iodesc_dp_l4dvar, mod_pio_netcdf::iodesc_dp_p2dvar, mod_pio_netcdf::iodesc_dp_p3dvar, mod_pio_netcdf::iodesc_dp_r2dfrc, mod_pio_netcdf::iodesc_dp_r2dhar, mod_pio_netcdf::iodesc_dp_r2dobc, mod_pio_netcdf::iodesc_dp_r2dvar, mod_pio_netcdf::iodesc_dp_r3dhar, mod_pio_netcdf::iodesc_dp_r3dobc, mod_pio_netcdf::iodesc_dp_r3dvar, mod_pio_netcdf::iodesc_dp_resid, mod_pio_netcdf::iodesc_dp_rtides, mod_pio_netcdf::iodesc_dp_rubar, mod_pio_netcdf::iodesc_dp_ruvel, mod_pio_netcdf::iodesc_dp_rvbar, mod_pio_netcdf::iodesc_dp_rvvel, mod_pio_netcdf::iodesc_dp_rzeta, mod_pio_netcdf::iodesc_dp_sworkd, mod_pio_netcdf::iodesc_dp_tkevar, mod_pio_netcdf::iodesc_dp_trcvar, mod_pio_netcdf::iodesc_dp_u2dfrc, mod_pio_netcdf::iodesc_dp_u2dhar, mod_pio_netcdf::iodesc_dp_u2dobc, mod_pio_netcdf::iodesc_dp_u2dvar, mod_pio_netcdf::iodesc_dp_u3dhar, mod_pio_netcdf::iodesc_dp_u3dobc, mod_pio_netcdf::iodesc_dp_u3dvar, mod_pio_netcdf::iodesc_dp_ubar, mod_pio_netcdf::iodesc_dp_uvel, mod_pio_netcdf::iodesc_dp_v2dfrc, mod_pio_netcdf::iodesc_dp_v2dhar, mod_pio_netcdf::iodesc_dp_v2dobc, mod_pio_netcdf::iodesc_dp_v2dvar, mod_pio_netcdf::iodesc_dp_v3dhar, mod_pio_netcdf::iodesc_dp_v3dobc, mod_pio_netcdf::iodesc_dp_v3dvar, mod_pio_netcdf::iodesc_dp_vbar, mod_pio_netcdf::iodesc_dp_vvel, mod_pio_netcdf::iodesc_dp_w3dvar, mod_pio_netcdf::iodesc_dp_zeta, mod_pio_netcdf::iodesc_sp_b3dvar, mod_pio_netcdf::iodesc_sp_bvec, mod_pio_netcdf::iodesc_sp_l3dvar, mod_pio_netcdf::iodesc_sp_l4dvar, mod_pio_netcdf::iodesc_sp_p2dvar, mod_pio_netcdf::iodesc_sp_p3dvar, mod_pio_netcdf::iodesc_sp_r2dfrc, mod_pio_netcdf::iodesc_sp_r2dhar, mod_pio_netcdf::iodesc_sp_r2dobc, mod_pio_netcdf::iodesc_sp_r2dvar, mod_pio_netcdf::iodesc_sp_r3dhar, mod_pio_netcdf::iodesc_sp_r3dobc, mod_pio_netcdf::iodesc_sp_r3dvar, mod_pio_netcdf::iodesc_sp_resid, mod_pio_netcdf::iodesc_sp_rtides, mod_pio_netcdf::iodesc_sp_rubar, mod_pio_netcdf::iodesc_sp_ruvel, mod_pio_netcdf::iodesc_sp_rvbar, mod_pio_netcdf::iodesc_sp_rvvel, mod_pio_netcdf::iodesc_sp_rzeta, mod_pio_netcdf::iodesc_sp_sworkd, mod_pio_netcdf::iodesc_sp_tkevar, mod_pio_netcdf::iodesc_sp_trcvar, mod_pio_netcdf::iodesc_sp_u2dfrc, mod_pio_netcdf::iodesc_sp_u2dhar, mod_pio_netcdf::iodesc_sp_u2dobc, mod_pio_netcdf::iodesc_sp_u2dvar, mod_pio_netcdf::iodesc_sp_u3dhar, mod_pio_netcdf::iodesc_sp_u3dobc, mod_pio_netcdf::iodesc_sp_u3dvar, mod_pio_netcdf::iodesc_sp_ubar, mod_pio_netcdf::iodesc_sp_uvel, mod_pio_netcdf::iodesc_sp_v2dfrc, mod_pio_netcdf::iodesc_sp_v2dhar, mod_pio_netcdf::iodesc_sp_v2dobc, mod_pio_netcdf::iodesc_sp_v2dvar, mod_pio_netcdf::iodesc_sp_v3dhar, mod_pio_netcdf::iodesc_sp_v3dobc, mod_pio_netcdf::iodesc_sp_v3dvar, mod_pio_netcdf::iodesc_sp_vbar, mod_pio_netcdf::iodesc_sp_vvel, mod_pio_netcdf::iodesc_sp_w3dvar, mod_pio_netcdf::iodesc_sp_zeta, mod_pio_netcdf::ipioroms, mod_param::l3dvar, mod_param::l4dvar, mod_parallel::master, mod_parallel::mymaster, mod_parallel::myrank, mod_param::n, mod_param::nbed, mod_param::ngrids, mod_pio_netcdf::npiocomps, mod_stepping::ntc, mod_param::ntilei, mod_param::ntilej, mod_parallel::numthreads, mod_parallel::ocn_comm_world, mod_parallel::outthread, mod_param::p2dvar, mod_param::p3dvar, mod_pio_netcdf::pio_base, mod_pio_netcdf::pio_numiotasks, mod_pio_netcdf::pio_stride, mod_pio_netcdf::piosystem, mod_param::r2dobc, mod_param::r2dvar, mod_param::r3dobc, mod_param::r3dvar, mod_param::u2dobc, mod_param::u2dvar, mod_param::u3dobc, mod_param::u3dvar, mod_param::v2dobc, mod_param::v2dvar, mod_param::v3dobc, mod_param::v3dvar, and mod_param::w3dvar.

Referenced by mod_arrays::roms_allocate_arrays().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ state_iodecomp()

subroutine, public set_pio_mod::state_iodecomp ( integer, intent(in) ng,
type (iosystem_desc_t), intent(in) iosystem,
integer, intent(in) iotype,
type (io_desc_t), intent(out) iodesc,
character (len=*) iovname,
integer, intent(in) ndims )

Definition at line 1582 of file set_pio.F.

1584!
1585!***********************************************************************
1586! !
1587! Sets the IO decomposition descriptor for ROMS packed state variable !
1588! types. !
1589! !
1590! On Input: !
1591! !
1592! ng Nested grid number (integer) !
1593! ioSystem PIO system descriptor (TYPE IOSystem_desc_t) !
1594! ioType PIO kind variable type (integer) !
1595! ioVname State variable name (string) !
1596! ndims Number of state variable dimensions (integer) !
1597! !
1598! On Output: !
1599! !
1600! ioDesc IO decomposition descriptor (TYPE io_desc_t) !
1601! !
1602!***********************************************************************
1603!
1604! Imported variable declarations.
1605!
1606 integer, intent(in) :: ng, ioType, ndims
1607!
1608 character (len=*) :: ioVname
1609!
1610 TYPE (IOSystem_desc_t), intent(in) :: ioSystem
1611 TYPE (io_desc_t), intent(out) :: ioDesc
1612!
1613! Local variable declarations.
1614!
1615 integer :: Is, Ie, Isize, Js, Je, Jsize, my_size
1616 integer :: Imin, Imax, Ioff, Jmin, Jmax, Joff
1617 integer :: i, ic, j, jc, np
1618
1619 integer(PIO_Offset_kind), allocatable :: map_decomp(:)
1620!
1621!-----------------------------------------------------------------------
1622! Set the PIO computational decomposition for ROMS packed state
1623! variables.
1624!-----------------------------------------------------------------------
1625!
1626 SELECT CASE (trim(iovname))
1627 CASE ('Bvec')
1628 is=nstr(ng)
1629 ie=nend(ng)
1630 js=1
1631 je=ncv
1632 ioff=0
1633 joff=1
1634 CASE ('resid')
1635 is=nstr(ng)
1636 ie=nend(ng)
1637 CASE ('SworkD')
1638 is=myrank*3*nstate(ng)+1
1639 ie=min(is+3*nstate(ng)-1, 3*mstate(ng))
1640 END SELECT
1641!
1642! Starting/ending I- and J-indices for each decomposition tile.
1643!
1644 IF (ndims.eq.1) THEN
1645 imin=is
1646 imax=ie
1647 isize=ie-is+1
1648 my_size=isize
1649 ELSE IF (ndims.eq.2) THEN
1650 imin=is
1651 imax=ie
1652 jmin=js
1653 jmax=je
1654 isize=ie-is+1
1655 jsize=je-js+1
1656 my_size=isize*jsize
1657 END IF
1658!
1659! Allocate 1D array for mapping of the storage order of the variable to
1660! its memory order.
1661!
1662 IF (.not.ALLOCATED(map_decomp)) THEN
1663 allocate ( map_decomp(my_size) )
1664 END IF
1665 map_decomp=0_pio_offset_kind
1666!
1667! Set variable decomposition mapping.
1668!
1669 IF (ndims.eq.1) THEN
1670 np=0
1671 DO i=imin,imax
1672 np=np+1
1673 map_decomp(np)=i
1674 END DO
1675 ELSE IF (ndims.eq.2) THEN
1676 np=0
1677 DO j=jmin,jmax
1678 jc=(j-joff)*isize
1679 DO i=imin,imax
1680 np=np+1
1681 ic=i+ioff+jc
1682 map_decomp(np)=ic
1683 END DO
1684 END DO
1685 END IF
1686!
1687! Set IO decomposition descriptor
1688!
1689 IF (ndims.eq.1) THEN
1690 CALL pio_initdecomp (iosystem, iotype, (/isize/), &
1691 & map_decomp, iodesc)
1692 ELSE IF (ndims.eq.2) THEN
1693 CALL pio_initdecomp (iosystem, iotype, (/isize,jsize/), &
1694 & map_decomp, iodesc)
1695 END IF
1696!
1697! Deallocate.
1698!
1699 IF (ALLOCATED(map_decomp)) deallocate (map_decomp)
1700!
1701 RETURN

References mod_param::mstate, mod_parallel::myrank, mod_storage::ncv, mod_param::nend, mod_param::nstate, and mod_param::nstr.

Referenced by wpoints_tile().

Here is the caller graph for this function: