/[MITgcm]/MITgcm/pkg/aim_v23/aim_write_phys.F
ViewVC logotype

Annotation of /MITgcm/pkg/aim_v23/aim_write_phys.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Fri Aug 4 22:27:46 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58o_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
new S/R AIM_WRITE_PHYS (replaces AIM_WRITE_LOCAL) to write AIM physics
 common-block variables ; Allows multi-threading with master-thread IO.

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_write_local.F,v 1.1 2002/11/22 17:17:03 jmc Exp $
2     C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: AIM_WRITE_PHYS
8     C !INTERFACE:
9     SUBROUTINE AIM_WRITE_PHYS(
10     I pref, suff, nNr, field,
11     I kLev, bi, bj, iRec, myIter, myThid )
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE AIM_WRITE_PHYS
15     C | o Write variable from AIM physics common block
16     C | (=> no overlap & nThreads) and reverse K index.
17     C *==========================================================*
18     C | Note: assume symetry in tiles per thread treatment
19     C *==========================================================*
20     C !USES
21     IMPLICIT NONE
22    
23     C == Global variables ===
24     #include "AIM_SIZE.h"
25    
26     #include "EEPARAMS.h"
27     c #include "PARAMS.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C == Routine arguments ==
31     C pref :: Prefix of the output file name
32     C suff :: Suffix of the output file name
33     C nNr :: 3rd dim. of the input field
34     C field :: Field (from aim-physics) to write
35     C kLev :: level index to write (0 = write all levels)
36     C bi,bj :: Tile index
37     C iRec :: reccord number in the output file
38     C myIter :: Current iteration number in simulation
39     C myThid :: Thread number for this instance of the routine
40     CHARACTER*(*) pref, suff
41     INTEGER nNr
42     _RL field(sNx,sNy,nNr,MAX_NO_THREADS)
43     INTEGER kLev, bi, bj, iRec, myIter, myThid
44    
45     #ifdef ALLOW_AIM
46    
47     C Functions
48     INTEGER ILNBLNK
49     EXTERNAL ILNBLNK
50    
51     C !LOCAL VARIABLES:
52     CHARACTER*(MAX_LEN_MBUF) msgBuf
53     _RL tmpFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
54     INTEGER iL
55     INTEGER i, j, k, Katm, nLoc
56     INTEGER ith, biLoc, bjLoc
57    
58     CEOP
59    
60     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61    
62     #ifdef LOCBIN_IO_THREAD_SAFE
63     C- safe for any thread to do IO
64     ith = myThid
65     biLoc = bi
66     bjLoc = bj
67     #else /* LOCBIN_IO_THREAD_SAFE */
68     C- master-thread does IO for all threads
69     _BARRIER
70     _BEGIN_MASTER( myThid )
71     DO ith=1,nThreads
72     biLoc = bi + myBxLo(ith) - 1
73     bjLoc = bj + myByLo(ith) - 1
74     #endif /* LOCBIN_IO_THREAD_SAFE */
75    
76     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
77    
78     C-- Check for argument list consistency
79     IF ( nNr.LT.1 .OR. nNr.GT.Nr ) THEN
80     iL = ILNBLNK( pref )
81     WRITE(msgBuf,'(A,I10,A,2I5,A,I4,2A)')
82     & 'AIM_WRITE_PHYS (it=', myIter, ' bi,bj=', bi,bj,
83     & ' iRec=', iRec, ' ): try to write: ', pref(1:iL)
84     CALL PRINT_ERROR( msgBuf, myThid )
85     WRITE(msgBuf,'(A,I4,A,I4)')
86     & 'AIM_WRITE_PHYS: 3rd dim.(field)=',nNr,' has to be <',Nr
87     CALL PRINT_ERROR( msgBuf , myThid)
88     STOP 'ABNORMAL END: S/R AIM_WRITE_PHYS'
89     ELSEIF ( kLev.NE.0 .AND. kLev.GT.nNr ) THEN
90     iL = ILNBLNK( pref )
91     WRITE(msgBuf,'(A,I10,A,2I5,A,I4,2A)')
92     & 'AIM_WRITE_PHYS (it=', myIter, ' bi,bj=', bi,bj,
93     & ' iRec=', iRec, ' ): try to write: ', pref(1:iL)
94     CALL PRINT_ERROR( msgBuf, myThid )
95     WRITE(msgBuf,'(A,I4,A,I4)')
96     & 'AIM_WRITE_PHYS: kLev=', kLev,
97     & ' out of bounds (dim=', nNr,' )'
98     CALL PRINT_ERROR( msgBuf , myThid)
99     STOP 'ABNORMAL END: S/R AIM_WRITE_PHYS'
100     ENDIF
101    
102     C-- Copy the input field into tempo. array:
103     nLoc = nNr
104     IF ( kLev.GE.1 .AND. kLev.LE.nNr ) THEN
105     nLoc = 1
106     DO j=1,sNy
107     DO i=1,sNx
108     tmpFld(i,j,1) = field(i,j,kLev,ith)
109     ENDDO
110     ENDDO
111     ELSEIF (nNr.EQ.Nr) THEN
112     C- Reverse K index:
113     DO k=1,Nr
114     Katm = _KD2KA( k )
115     DO j=1,sNy
116     DO i=1,sNx
117     tmpFld(i,j,k) = field(i,j,Katm,ith)
118     ENDDO
119     ENDDO
120     ENDDO
121     ELSE
122     C- Do simple copy
123     DO k=1,nNr
124     DO j=1,sNy
125     DO i=1,sNx
126     tmpFld(i,j,k) = field(i,j,k,ith)
127     ENDDO
128     ENDDO
129     ENDDO
130     ENDIF
131    
132     C-- Write to file:
133     CALL WRITE_LOCAL_RL( pref, suff, nLoc, tmpFld,
134     & biLoc, bjLoc, iRec, myIter, myThid )
135    
136     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
137    
138     #ifndef LOCBIN_IO_THREAD_SAFE
139     ENDDO
140     _END_MASTER( myThid )
141     _BARRIER
142     #endif /* ndef LOCBIN_IO_THREAD_SAFE */
143    
144     #endif /* ALLOW_AIM */
145     RETURN
146     END

  ViewVC Help
Powered by ViewVC 1.1.22