3 |
|
|
4 |
#include "MDSIO_OPTIONS.h" |
#include "MDSIO_OPTIONS.h" |
5 |
|
|
6 |
C The five "public" routines supplied here are: |
C-- File mdsio_gl.F: Routines to handle mid-level I/O interface. |
7 |
C |
C-- Contents |
8 |
C MDSREADFIELD - read model field from direct access global or tiled MDS file |
C-- o MDSREADFIELD_3D_GL |
9 |
C MDSWRITEFIELD - write model field to direct access global or tiled MDS file |
C-- o MDSWRITEFIELD_3D_GL |
10 |
C MDSFINDUNIT - returns an available (unused) I/O channel |
C-- o MDSREADFIELD_2D_GL |
11 |
C MDSREADVECTOR - read vector from direct access global or tiled MDS file |
C-- o MDSWRITEFIELD_2D_GL |
12 |
C MDSWRITEVECTOR - write vector to direct access global or tiled MDS file |
|
13 |
C |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
|
C all other routines are "private" to these utilities and ought |
|
|
C not be accessed directly from the main code. |
|
|
C |
|
|
C Created: 03/16/99 adcroft@mit.edu |
|
|
C Modified: 03/23/99 adcroft@mit.edu |
|
|
C To work with multiple records |
|
|
C Modified: 03/29/99 eckert@mit.edu |
|
|
C Added arbitrary vector capability |
|
|
C Modified: 07/27/99 eckert@mit.edu |
|
|
C Customized for state estimation (--> active_file_control.F) |
|
|
C this relates only to *mdsreadvector* and *mdswritevector* |
|
|
C Modified: 07/28/99 eckert@mit.edu |
|
|
C inserted calls to *print_message* and *print_error* |
|
|
C |
|
|
C To be modified to work with MITgcmuv message routines. |
|
14 |
|
|
|
C======================================================================= |
|
15 |
SUBROUTINE MDSREADFIELD_3D_GL( |
SUBROUTINE MDSREADFIELD_3D_GL( |
16 |
I fName, |
I fName, |
17 |
I filePrec, |
I filePrec, |
23 |
C |
C |
24 |
C Arguments: |
C Arguments: |
25 |
C |
C |
26 |
C fName string base name for file to read |
C fName (string) :: base name for file to read |
27 |
C filePrec integer number of bits per word in file (32 or 64) |
C filePrec (integer) :: number of bits per word in file (32 or 64) |
28 |
C arrType char(2) declaration of "arr": either "RS" or "RL" |
C arrType (char(2)) :: type of array "arr": either "RS" or "RL" |
29 |
C nNz integer size of third dimension: normally either 1 or Nr |
C nNz (integer) :: size of third dimension: normally either 1 or Nr |
30 |
C arr RS/RL array to read into, arr(:,:,nNz,:,:) |
C arr (RS/RL) :: array to read into, arr(:,:,nNz,:,:) |
31 |
C irecord integer record number to read |
C irecord (integer) :: record number to read |
32 |
C myThid integer thread identifier |
C myThid (integer) :: thread identifier |
33 |
C |
C |
34 |
C MDSREADFIELD first checks to see if the file "fName" exists, then |
C MDSREADFIELD first checks to see if the file "fName" exists, then |
35 |
C if the file "fName.data" exists and finally the tiled files of the |
C if the file "fName.data" exists and finally the tiled files of the |
52 |
C Global variables / common blocks |
C Global variables / common blocks |
53 |
#include "SIZE.h" |
#include "SIZE.h" |
54 |
#include "EEPARAMS.h" |
#include "EEPARAMS.h" |
|
#include "EESUPPORT.h" |
|
55 |
#include "PARAMS.h" |
#include "PARAMS.h" |
56 |
|
|
57 |
C Routine arguments |
C Routine arguments |
62 |
_RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,Nr) |
_RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,Nr) |
63 |
integer irecord |
integer irecord |
64 |
integer myThid |
integer myThid |
65 |
|
|
66 |
|
#ifdef ALLOW_CTRL |
67 |
|
|
68 |
C Functions |
C Functions |
69 |
integer ILNBLNK |
integer ILNBLNK |
70 |
integer MDS_RECLEN |
integer MDS_RECLEN |
89 |
Real*8 global(Nx,Ny) |
Real*8 global(Nx,Ny) |
90 |
c _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
c _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
91 |
cph-usesingle) |
cph-usesingle) |
92 |
|
CMM( |
93 |
|
integer pIL |
94 |
|
CMM) |
95 |
|
|
96 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
97 |
|
|
114 |
globalFile = .FALSE. |
globalFile = .FALSE. |
115 |
fileIsOpen = .FALSE. |
fileIsOpen = .FALSE. |
116 |
IL=ILNBLNK( fName ) |
IL=ILNBLNK( fName ) |
117 |
|
CMM( |
118 |
|
pIL = ILNBLNK( mdsioLocalDir ) |
119 |
|
CMM) |
120 |
|
CMM( |
121 |
|
C Assign special directory |
122 |
|
if ( pIL.NE.0 ) then |
123 |
|
write(fName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL) |
124 |
|
endif |
125 |
|
CMM) |
126 |
|
|
127 |
C Assign a free unit number as the I/O channel for this routine |
C Assign a free unit number as the I/O channel for this routine |
128 |
call MDSFINDUNIT( dUnit, mythid ) |
call MDSFINDUNIT( dUnit, mythid ) |
130 |
if ( useSingleCPUIO ) then |
if ( useSingleCPUIO ) then |
131 |
|
|
132 |
#ifdef ALLOW_USE_MPI |
#ifdef ALLOW_USE_MPI |
133 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
134 |
#else |
#else |
135 |
IF ( .TRUE. ) THEN |
IF ( .TRUE. ) THEN |
136 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
154 |
open( dUnit, file=dataFName, status='old', |
open( dUnit, file=dataFName, status='old', |
155 |
& access='direct', recl=length_of_rec ) |
& access='direct', recl=length_of_rec ) |
156 |
else |
else |
157 |
write(msgbuf,'(2a)') |
write(msgbuf,'(2a)') |
158 |
& ' MDSREADFIELD: filename: ',dataFName(1:IL) |
& ' MDSREADFIELD: filename: ',dataFName(1:IL) |
159 |
call print_message( msgbuf, standardmessageunit, |
call print_message( msgbuf, standardmessageunit, |
160 |
& SQUEEZE_RIGHT , mythid) |
& SQUEEZE_RIGHT , mythid) |
211 |
fileIsOpen=.TRUE. |
fileIsOpen=.TRUE. |
212 |
endif |
endif |
213 |
|
|
214 |
C Loop over all processors |
C Loop over all processors |
215 |
do jp=1,nPy |
do jp=1,nPy |
216 |
do ip=1,nPx |
do ip=1,nPx |
217 |
C Loop over all tiles |
C Loop over all tiles |
337 |
DO k=1,nNz |
DO k=1,nNz |
338 |
|
|
339 |
#ifdef ALLOW_USE_MPI |
#ifdef ALLOW_USE_MPI |
340 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
341 |
#else |
#else |
342 |
IF ( .TRUE. ) THEN |
IF ( .TRUE. ) THEN |
343 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
395 |
|
|
396 |
_END_MASTER( myThid ) |
_END_MASTER( myThid ) |
397 |
|
|
398 |
|
#else /* ALLOW_CTRL */ |
399 |
|
STOP 'ABNORMAL END: S/R MDSREADFIELD_3D_GL is empty' |
400 |
|
#endif /* ALLOW_CTRL */ |
401 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
402 |
return |
RETURN |
403 |
end |
END |
404 |
C======================================================================= |
|
405 |
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
406 |
|
|
|
C======================================================================= |
|
407 |
SUBROUTINE MDSWRITEFIELD_3D_GL( |
SUBROUTINE MDSWRITEFIELD_3D_GL( |
408 |
I fName, |
I fName, |
409 |
I filePrec, |
I filePrec, |
416 |
C |
C |
417 |
C Arguments: |
C Arguments: |
418 |
C |
C |
419 |
C fName string base name for file to written |
C fName (string) :: base name for file to write |
420 |
C filePrec integer number of bits per word in file (32 or 64) |
C filePrec (integer) :: number of bits per word in file (32 or 64) |
421 |
C arrType char(2) declaration of "arr": either "RS" or "RL" |
C arrType (char(2)) :: type of array "arr": either "RS" or "RL" |
422 |
C nNz integer size of third dimension: normally either 1 or Nr |
C nNz (integer) :: size of third dimension: normally either 1 or Nr |
423 |
C arr RS/RL array to write, arr(:,:,nNz,:,:) |
C arr (RS/RL) :: array to write, arr(:,:,nNz,:,:) |
424 |
C irecord integer record number to read |
C irecord (integer) :: record number to write |
425 |
C myIter integer time step number |
C myIter (integer) :: time step number |
426 |
C myThid integer thread identifier |
C myThid (integer) :: thread identifier |
427 |
C |
C |
428 |
C MDSWRITEFIELD creates either a file of the form "fName.data" and |
C MDSWRITEFIELD creates either a file of the form "fName.data" and |
429 |
C "fName.meta" if the logical flag "globalFile" is set true. Otherwise |
C "fName.meta" if the logical flag "globalFile" is set true. Otherwise |
454 |
C Global variables / common blocks |
C Global variables / common blocks |
455 |
#include "SIZE.h" |
#include "SIZE.h" |
456 |
#include "EEPARAMS.h" |
#include "EEPARAMS.h" |
|
#include "EESUPPORT.h" |
|
457 |
#include "PARAMS.h" |
#include "PARAMS.h" |
458 |
|
|
459 |
C Routine arguments |
C Routine arguments |
468 |
integer irecord |
integer irecord |
469 |
integer myIter |
integer myIter |
470 |
integer myThid |
integer myThid |
471 |
|
|
472 |
|
#ifdef ALLOW_CTRL |
473 |
|
|
474 |
C Functions |
C Functions |
475 |
integer ILNBLNK |
integer ILNBLNK |
476 |
integer MDS_RECLEN |
integer MDS_RECLEN |
480 |
Real*4 r4seg(sNx) |
Real*4 r4seg(sNx) |
481 |
Real*8 r8seg(sNx) |
Real*8 r8seg(sNx) |
482 |
_RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy) |
_RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy) |
483 |
integer dimList(3,3),ndims |
INTEGER dimList(3,3), nDims, map2gl(2) |
484 |
|
_RL dummyRL(1) |
485 |
|
CHARACTER*8 blank8c |
486 |
integer length_of_rec |
integer length_of_rec |
487 |
logical fileIsOpen |
logical fileIsOpen |
488 |
character*(max_len_mbuf) msgbuf |
character*(max_len_mbuf) msgbuf |
498 |
Real*8 global(Nx,Ny) |
Real*8 global(Nx,Ny) |
499 |
#endif |
#endif |
500 |
cph-usesingle) |
cph-usesingle) |
501 |
|
CMM( |
502 |
|
integer pIL |
503 |
|
CMM) |
504 |
|
|
505 |
|
DATA dummyRL(1) / 0. _d 0 / |
506 |
|
DATA blank8c / ' ' / |
507 |
|
|
508 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
509 |
|
|
525 |
C Assume nothing |
C Assume nothing |
526 |
fileIsOpen=.FALSE. |
fileIsOpen=.FALSE. |
527 |
IL=ILNBLNK( fName ) |
IL=ILNBLNK( fName ) |
528 |
|
CMM( |
529 |
|
pIL = ILNBLNK( mdsioLocalDir ) |
530 |
|
CMM) |
531 |
|
CMM( |
532 |
|
C Assign special directory |
533 |
|
if ( pIL.NE.0 ) then |
534 |
|
write(fName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL) |
535 |
|
endif |
536 |
|
CMM) |
537 |
|
|
538 |
C Assign a free unit number as the I/O channel for this routine |
C Assign a free unit number as the I/O channel for this routine |
539 |
call MDSFINDUNIT( dUnit, mythid ) |
call MDSFINDUNIT( dUnit, mythid ) |
547 |
|
|
548 |
C Master thread of process 0, only, opens a global file |
C Master thread of process 0, only, opens a global file |
549 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
550 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
551 |
write(dataFname,'(2a)') fName(1:IL),'.data' |
write(dataFname,'(2a)') fName(1:IL),'.data' |
552 |
length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid) |
length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid) |
553 |
if (irecord .EQ. 1) then |
if (irecord .EQ. 1) then |
562 |
|
|
563 |
C Gather array and write it to file, one vertical level at a time |
C Gather array and write it to file, one vertical level at a time |
564 |
DO k=1,nNz |
DO k=1,nNz |
565 |
C Loop over all processors |
C Loop over all processors |
566 |
do jp=1,nPy |
do jp=1,nPy |
567 |
do ip=1,nPx |
do ip=1,nPx |
568 |
DO bj = myByLo(myThid), myByHi(myThid) |
DO bj = myByLo(myThid), myByHi(myThid) |
579 |
enddo |
enddo |
580 |
enddo |
enddo |
581 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
582 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
583 |
irec=k+nNz*(irecord-1) |
irec=k+nNz*(irecord-1) |
584 |
if (filePrec .eq. precFloat32) then |
if (filePrec .eq. precFloat32) then |
585 |
DO J=1,Ny |
DO J=1,Ny |
613 |
|
|
614 |
C Close data-file and create meta-file |
C Close data-file and create meta-file |
615 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
616 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
617 |
close( dUnit ) |
close( dUnit ) |
618 |
write(metaFName,'(2a)') fName(1:IL),'.meta' |
write(metaFName,'(2a)') fName(1:IL),'.meta' |
619 |
dimList(1,1)=Nx |
dimList(1,1)=Nx |
625 |
dimList(1,3)=nNz |
dimList(1,3)=nNz |
626 |
dimList(2,3)=1 |
dimList(2,3)=1 |
627 |
dimList(3,3)=nNz |
dimList(3,3)=nNz |
628 |
ndims=3 |
nDims=3 |
629 |
if (nNz .EQ. 1) ndims=2 |
if (nNz .EQ. 1) nDims=2 |
630 |
call MDSWRITEMETA( metaFName, dataFName, |
map2gl(1) = 0 |
631 |
& filePrec, ndims, dimList, irecord, myIter, mythid ) |
map2gl(2) = 1 |
632 |
|
CALL MDS_WRITE_META( |
633 |
|
I metaFName, dataFName, the_run_name, ' ', |
634 |
|
I filePrec, nDims, dimList, map2gl, 0, blank8c, |
635 |
|
I 0, dummyRL, irecord, myIter, myThid ) |
636 |
ENDIF |
ENDIF |
637 |
_END_MASTER( myThid ) |
_END_MASTER( myThid ) |
638 |
C To be safe, make other processes wait for I/O completion |
C To be safe, make other processes wait for I/O completion |
643 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
644 |
cph-usesingle) |
cph-usesingle) |
645 |
|
|
646 |
C Loop over all processors |
C Loop over all processors |
647 |
do jp=1,nPy |
do jp=1,nPy |
648 |
do ip=1,nPx |
do ip=1,nPx |
649 |
C Loop over all tiles |
C Loop over all tiles |
739 |
dimList(1,3)=Nr |
dimList(1,3)=Nr |
740 |
dimList(2,3)=1 |
dimList(2,3)=1 |
741 |
dimList(3,3)=Nr |
dimList(3,3)=Nr |
742 |
ndims=3 |
nDims=3 |
743 |
if (Nr .EQ. 1) ndims=2 |
if (Nr .EQ. 1) nDims=2 |
744 |
call MDSWRITEMETA( metaFName, dataFName, |
map2gl(1) = 0 |
745 |
& filePrec, ndims, dimList, irecord, myIter, mythid ) |
map2gl(2) = 1 |
746 |
|
CALL MDS_WRITE_META( |
747 |
|
I metaFName, dataFName, the_run_name, ' ', |
748 |
|
I filePrec, nDims, dimList, map2gl, 0, blank8c, |
749 |
|
I 0, dummyRL, irecord, myIter, myThid ) |
750 |
C End of bi,bj loops |
C End of bi,bj loops |
751 |
enddo |
enddo |
752 |
enddo |
enddo |
763 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
764 |
cph-usesingle) |
cph-usesingle) |
765 |
|
|
766 |
|
#else /* ALLOW_CTRL */ |
767 |
|
STOP 'ABNORMAL END: S/R MDSWRITEFIELD_3D_GL is empty' |
768 |
|
#endif /* ALLOW_CTRL */ |
769 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
770 |
return |
RETURN |
771 |
end |
END |
772 |
C======================================================================= |
|
773 |
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
774 |
|
|
|
C======================================================================= |
|
775 |
SUBROUTINE MDSREADFIELD_2D_GL( |
SUBROUTINE MDSREADFIELD_2D_GL( |
776 |
I fName, |
I fName, |
777 |
I filePrec, |
I filePrec, |
783 |
C |
C |
784 |
C Arguments: |
C Arguments: |
785 |
C |
C |
786 |
C fName string base name for file to read |
C fName (string) :: base name for file to read |
787 |
C filePrec integer number of bits per word in file (32 or 64) |
C filePrec (integer) :: number of bits per word in file (32 or 64) |
788 |
C arrType char(2) declaration of "arr": either "RS" or "RL" |
C arrType (char(2)) :: type of array "arr": either "RS" or "RL" |
789 |
C nNz integer size of third dimension: normally either 1 or Nr |
C nNz (integer) :: size of third dimension: normally either 1 or Nr |
790 |
C arr RS/RL array to read into, arr(:,:,nNz,:,:) |
C arr (RS/RL) :: array to read into, arr(:,:,nNz,:,:) |
791 |
C irecord integer record number to read |
C irecord (integer) :: record number to read |
792 |
C myThid integer thread identifier |
C myThid (integer) :: thread identifier |
793 |
C |
C |
794 |
C MDSREADFIELD first checks to see if the file "fName" exists, then |
C MDSREADFIELD first checks to see if the file "fName" exists, then |
795 |
C if the file "fName.data" exists and finally the tiled files of the |
C if the file "fName.data" exists and finally the tiled files of the |
812 |
C Global variables / common blocks |
C Global variables / common blocks |
813 |
#include "SIZE.h" |
#include "SIZE.h" |
814 |
#include "EEPARAMS.h" |
#include "EEPARAMS.h" |
|
#include "EESUPPORT.h" |
|
815 |
#include "PARAMS.h" |
#include "PARAMS.h" |
816 |
|
|
817 |
C Routine arguments |
C Routine arguments |
823 |
_RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nLocz) |
_RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nLocz) |
824 |
integer irecord |
integer irecord |
825 |
integer myThid |
integer myThid |
826 |
|
|
827 |
|
#ifdef ALLOW_CTRL |
828 |
|
|
829 |
C Functions |
C Functions |
830 |
integer ILNBLNK |
integer ILNBLNK |
831 |
integer MDS_RECLEN |
integer MDS_RECLEN |
850 |
Real*8 global(Nx,Ny) |
Real*8 global(Nx,Ny) |
851 |
c _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
c _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
852 |
cph-usesingle) |
cph-usesingle) |
853 |
|
CMM( |
854 |
|
integer pIL |
855 |
|
CMM) |
856 |
|
|
857 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
858 |
|
|
875 |
globalFile = .FALSE. |
globalFile = .FALSE. |
876 |
fileIsOpen = .FALSE. |
fileIsOpen = .FALSE. |
877 |
IL=ILNBLNK( fName ) |
IL=ILNBLNK( fName ) |
878 |
|
CMM( |
879 |
|
pIL = ILNBLNK( mdsioLocalDir ) |
880 |
|
CMM) |
881 |
|
CMM( |
882 |
|
C Assign special directory |
883 |
|
if ( pIL.NE.0 ) then |
884 |
|
write(fName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL) |
885 |
|
endif |
886 |
|
CMM) |
887 |
|
|
888 |
C Assign a free unit number as the I/O channel for this routine |
C Assign a free unit number as the I/O channel for this routine |
889 |
call MDSFINDUNIT( dUnit, mythid ) |
call MDSFINDUNIT( dUnit, mythid ) |
892 |
|
|
893 |
C master thread of process 0, only, opens a global file |
C master thread of process 0, only, opens a global file |
894 |
#ifdef ALLOW_USE_MPI |
#ifdef ALLOW_USE_MPI |
895 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
896 |
#else |
#else |
897 |
IF ( .TRUE. ) THEN |
IF ( .TRUE. ) THEN |
898 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
916 |
open( dUnit, file=dataFName, status='old', |
open( dUnit, file=dataFName, status='old', |
917 |
& access='direct', recl=length_of_rec ) |
& access='direct', recl=length_of_rec ) |
918 |
else |
else |
919 |
write(msgbuf,'(2a)') |
write(msgbuf,'(2a)') |
920 |
& ' MDSREADFIELD: filename: ',dataFName(1:IL) |
& ' MDSREADFIELD: filename: ',dataFName(1:IL) |
921 |
call print_message( msgbuf, standardmessageunit, |
call print_message( msgbuf, standardmessageunit, |
922 |
& SQUEEZE_RIGHT , mythid) |
& SQUEEZE_RIGHT , mythid) |
972 |
fileIsOpen=.TRUE. |
fileIsOpen=.TRUE. |
973 |
endif |
endif |
974 |
|
|
975 |
C Loop over all processors |
C Loop over all processors |
976 |
do jp=1,nPy |
do jp=1,nPy |
977 |
do ip=1,nPx |
do ip=1,nPx |
978 |
C Loop over all tiles |
C Loop over all tiles |
1098 |
DO k=1,nLocz |
DO k=1,nLocz |
1099 |
|
|
1100 |
#ifdef ALLOW_USE_MPI |
#ifdef ALLOW_USE_MPI |
1101 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
1102 |
#else |
#else |
1103 |
IF ( .TRUE. ) THEN |
IF ( .TRUE. ) THEN |
1104 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
1156 |
|
|
1157 |
_END_MASTER( myThid ) |
_END_MASTER( myThid ) |
1158 |
|
|
1159 |
|
#else /* ALLOW_CTRL */ |
1160 |
|
STOP 'ABNORMAL END: S/R MDSREADFIELD_2D_GL is empty' |
1161 |
|
#endif /* ALLOW_CTRL */ |
1162 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
1163 |
return |
RETURN |
1164 |
end |
END |
1165 |
C======================================================================= |
|
1166 |
|
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
1167 |
|
|
|
C======================================================================= |
|
1168 |
SUBROUTINE MDSWRITEFIELD_2D_GL( |
SUBROUTINE MDSWRITEFIELD_2D_GL( |
1169 |
I fName, |
I fName, |
1170 |
I filePrec, |
I filePrec, |
1177 |
C |
C |
1178 |
C Arguments: |
C Arguments: |
1179 |
C |
C |
1180 |
C fName string base name for file to written |
C fName (string) :: base name for file to write |
1181 |
C filePrec integer number of bits per word in file (32 or 64) |
C filePrec (integer) :: number of bits per word in file (32 or 64) |
1182 |
C arrType char(2) declaration of "arr": either "RS" or "RL" |
C arrType (char(2)) :: type of array "arr": either "RS" or "RL" |
1183 |
C nNz integer size of third dimension: normally either 1 or Nr |
C nNz (integer) :: size of third dimension: normally either 1 or Nr |
1184 |
C arr RS/RL array to write, arr(:,:,nNz,:,:) |
C arr (RS/RL) :: array to write, arr(:,:,nNz,:,:) |
1185 |
C irecord integer record number to read |
C irecord (integer) :: record number to write |
1186 |
C myIter integer time step number |
C myIter (integer) :: time step number |
1187 |
C myThid integer thread identifier |
C myThid (integer) :: thread identifier |
1188 |
C |
C |
1189 |
C MDSWRITEFIELD creates either a file of the form "fName.data" and |
C MDSWRITEFIELD creates either a file of the form "fName.data" and |
1190 |
C "fName.meta" if the logical flag "globalFile" is set true. Otherwise |
C "fName.meta" if the logical flag "globalFile" is set true. Otherwise |
1215 |
C Global variables / common blocks |
C Global variables / common blocks |
1216 |
#include "SIZE.h" |
#include "SIZE.h" |
1217 |
#include "EEPARAMS.h" |
#include "EEPARAMS.h" |
|
#include "EESUPPORT.h" |
|
1218 |
#include "PARAMS.h" |
#include "PARAMS.h" |
1219 |
|
|
1220 |
C Routine arguments |
C Routine arguments |
1230 |
integer irecord |
integer irecord |
1231 |
integer myIter |
integer myIter |
1232 |
integer myThid |
integer myThid |
1233 |
|
|
1234 |
|
#ifdef ALLOW_CTRL |
1235 |
|
|
1236 |
C Functions |
C Functions |
1237 |
integer ILNBLNK |
integer ILNBLNK |
1238 |
integer MDS_RECLEN |
integer MDS_RECLEN |
1242 |
Real*4 r4seg(sNx) |
Real*4 r4seg(sNx) |
1243 |
Real*8 r8seg(sNx) |
Real*8 r8seg(sNx) |
1244 |
_RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy) |
_RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy) |
1245 |
integer dimList(3,3),ndims |
INTEGER dimList(3,3), nDims, map2gl(2) |
1246 |
|
_RL dummyRL(1) |
1247 |
|
CHARACTER*8 blank8c |
1248 |
integer length_of_rec |
integer length_of_rec |
1249 |
logical fileIsOpen |
logical fileIsOpen |
1250 |
character*(max_len_mbuf) msgbuf |
character*(max_len_mbuf) msgbuf |
1260 |
Real*8 global(Nx,Ny) |
Real*8 global(Nx,Ny) |
1261 |
#endif |
#endif |
1262 |
cph-usesingle) |
cph-usesingle) |
1263 |
|
CMM( |
1264 |
|
integer pIL |
1265 |
|
CMM) |
1266 |
|
|
1267 |
|
DATA dummyRL(1) / 0. _d 0 / |
1268 |
|
DATA blank8c / ' ' / |
1269 |
|
|
1270 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
1271 |
|
|
1287 |
C Assume nothing |
C Assume nothing |
1288 |
fileIsOpen=.FALSE. |
fileIsOpen=.FALSE. |
1289 |
IL=ILNBLNK( fName ) |
IL=ILNBLNK( fName ) |
1290 |
|
CMM( |
1291 |
|
pIL = ILNBLNK( mdsioLocalDir ) |
1292 |
|
CMM) |
1293 |
|
CMM( |
1294 |
|
C Assign special directory |
1295 |
|
if ( pIL.NE.0 ) then |
1296 |
|
write(fName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL) |
1297 |
|
endif |
1298 |
|
CMM) |
1299 |
|
|
1300 |
C Assign a free unit number as the I/O channel for this routine |
C Assign a free unit number as the I/O channel for this routine |
1301 |
call MDSFINDUNIT( dUnit, mythid ) |
call MDSFINDUNIT( dUnit, mythid ) |
1310 |
|
|
1311 |
C Master thread of process 0, only, opens a global file |
C Master thread of process 0, only, opens a global file |
1312 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
1313 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
1314 |
write(dataFname,'(2a)') fName(1:IL),'.data' |
write(dataFname,'(2a)') fName(1:IL),'.data' |
1315 |
length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid) |
length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid) |
1316 |
if (irecord .EQ. 1) then |
if (irecord .EQ. 1) then |
1325 |
|
|
1326 |
C Gather array and write it to file, one vertical level at a time |
C Gather array and write it to file, one vertical level at a time |
1327 |
DO k=1,nLocz |
DO k=1,nLocz |
1328 |
C Loop over all processors |
C Loop over all processors |
1329 |
do jp=1,nPy |
do jp=1,nPy |
1330 |
do ip=1,nPx |
do ip=1,nPx |
1331 |
DO bj = myByLo(myThid), myByHi(myThid) |
DO bj = myByLo(myThid), myByHi(myThid) |
1342 |
enddo |
enddo |
1343 |
enddo |
enddo |
1344 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
1345 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
1346 |
irec=k+nLocz*(irecord-1) |
irec=k+nLocz*(irecord-1) |
1347 |
if (filePrec .eq. precFloat32) then |
if (filePrec .eq. precFloat32) then |
1348 |
DO J=1,Ny |
DO J=1,Ny |
1376 |
|
|
1377 |
C Close data-file and create meta-file |
C Close data-file and create meta-file |
1378 |
_BEGIN_MASTER( myThid ) |
_BEGIN_MASTER( myThid ) |
1379 |
IF( mpiMyId .EQ. 0 ) THEN |
IF( myProcId .EQ. 0 ) THEN |
1380 |
close( dUnit ) |
close( dUnit ) |
1381 |
write(metaFName,'(2a)') fName(1:IL),'.meta' |
write(metaFName,'(2a)') fName(1:IL),'.meta' |
1382 |
dimList(1,1)=Nx |
dimList(1,1)=Nx |
1388 |
dimList(1,3)=nLocz |
dimList(1,3)=nLocz |
1389 |
dimList(2,3)=1 |
dimList(2,3)=1 |
1390 |
dimList(3,3)=nLocz |
dimList(3,3)=nLocz |
1391 |
ndims=3 |
nDims=3 |
1392 |
if (nLocz .EQ. 1) ndims=2 |
if (nLocz .EQ. 1) nDims=2 |
1393 |
call MDSWRITEMETA( metaFName, dataFName, |
map2gl(1) = 0 |
1394 |
& filePrec, ndims, dimList, irecord, myIter, mythid ) |
map2gl(2) = 1 |
1395 |
|
CALL MDS_WRITE_META( |
1396 |
|
I metaFName, dataFName, the_run_name, ' ', |
1397 |
|
I filePrec, nDims, dimList, map2gl, 0, blank8c, |
1398 |
|
I 0, dummyRL, irecord, myIter, myThid ) |
1399 |
ENDIF |
ENDIF |
1400 |
_END_MASTER( myThid ) |
_END_MASTER( myThid ) |
1401 |
C To be safe, make other processes wait for I/O completion |
C To be safe, make other processes wait for I/O completion |
1406 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
1407 |
cph-usesingle) |
cph-usesingle) |
1408 |
|
|
1409 |
C Loop over all processors |
C Loop over all processors |
1410 |
do jp=1,nPy |
do jp=1,nPy |
1411 |
do ip=1,nPx |
do ip=1,nPx |
1412 |
C Loop over all tiles |
C Loop over all tiles |
1502 |
dimList(1,3)=Nr |
dimList(1,3)=Nr |
1503 |
dimList(2,3)=1 |
dimList(2,3)=1 |
1504 |
dimList(3,3)=Nr |
dimList(3,3)=Nr |
1505 |
ndims=3 |
nDims=3 |
1506 |
if (nLocz .EQ. 1) ndims=2 |
if (nLocz .EQ. 1) nDims=2 |
1507 |
call MDSWRITEMETA( metaFName, dataFName, |
map2gl(1) = 0 |
1508 |
& filePrec, ndims, dimList, irecord, myIter, mythid ) |
map2gl(2) = 1 |
1509 |
|
CALL MDS_WRITE_META( |
1510 |
|
I metaFName, dataFName, the_run_name, ' ', |
1511 |
|
I filePrec, nDims, dimList, map2gl, 0, blank8c, |
1512 |
|
I 0, dummyRL, irecord, myIter, myThid ) |
1513 |
C End of bi,bj loops |
C End of bi,bj loops |
1514 |
enddo |
enddo |
1515 |
enddo |
enddo |
1524 |
endif |
endif |
1525 |
#endif /* ALLOW_USE_MPI */ |
#endif /* ALLOW_USE_MPI */ |
1526 |
|
|
1527 |
|
#else /* ALLOW_CTRL */ |
1528 |
|
STOP 'ABNORMAL END: S/R MDSWRITEFIELD_2D_GL is empty' |
1529 |
|
#endif /* ALLOW_CTRL */ |
1530 |
C ------------------------------------------------------------------ |
C ------------------------------------------------------------------ |
1531 |
return |
RETURN |
1532 |
end |
END |
|
C======================================================================= |
|