/[MITgcm]/MITgcm/model/src/ini_salt.F
ViewVC logotype

Diff of /MITgcm/model/src/ini_salt.F

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

revision 1.7 by cnh, Fri Nov 6 22:44:47 1998 UTC revision 1.23 by jmc, Mon Jan 18 19:37:35 2010 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CStartOfInterface  CBOP
8        SUBROUTINE INI_SALT ( myThid )  C     !ROUTINE: INI_SALT
9  C     /==========================================================\  C     !INTERFACE:
10  C     | SUBROUTINE INI_SALT                                      |        SUBROUTINE INI_SALT( myThid )
11  C     | o Set model initial salinity field.                      |  C     !DESCRIPTION: \bv
12  C     |==========================================================|  C     *==========================================================*
13  C     | There are several options for setting the initial        |  C     | SUBROUTINE INI_SALT
14  C     | temperature file                                         |  C     | o Set model initial salinity field.
15  C     |  1. Inline code                                          |  C     *==========================================================*
16  C     |  2. Vertical profile ( uniform S in X and Y )            |  C     | There are several options for setting the initial
17  C     |  3. Three-dimensional data from a file. For example from |  C     | temperature file
18  C     |     Levitus or from a checkpoint file from a previous    |  C     |  1. Inline code
19  C     |     integration.                                         |  C     |  2. Vertical profile ( uniform S in X and Y )
20  C     | In addition to setting the salinity field we also        |  C     |  3. Three-dimensional data from a file. For example from
21  C     | set the initial salinity tendency term here.             |  C     |     Levitus or from a checkpoint file from a previous
22  C     \==========================================================/  C     |     integration.
23    C     | In addition to setting the salinity field we also
24    C     | set the initial salinity tendency term here.
25    C     *==========================================================*
26    C     \ev
27    
28    C     !USES:
29          IMPLICIT NONE
30  C     === Global variables ===  C     === Global variables ===
31  #include "SIZE.h"  #include "SIZE.h"
32  #include "EEPARAMS.h"  #include "EEPARAMS.h"
33  #include "PARAMS.h"  #include "PARAMS.h"
34  #include "GRID.h"  #include "GRID.h"
35  #include "DYNVARS.h"  #include "DYNVARS.h"
36    #ifdef ALLOW_MNC
37    #include "MNC_PARAMS.h"
38    #endif
39    
40    C     !INPUT/OUTPUT PARAMETERS:
41  C     == Routine arguments ==  C     == Routine arguments ==
42  C     myThid -  Number of this instance of INI_SALT  C     myThid :: Number of this instance of INI_SALT
43        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
44    
45    C     !LOCAL VARIABLES:
46  C     == Local variables ==  C     == Local variables ==
47  C     iC, jC - Center of domain  C     bi,bj  :: Tile indices
48  C     iD, jD - Disitance from domain center.  C     i,j,k  :: Loop counters
 C     rad    - Radius of initial patch  
 C     rD     - Radial displacement of point I,J  
 C     iG, jG - Global coordinate index  
 C     bi,bj  - Loop counters  
 C     I,J,K  
       INTEGER iC, jC, iD, jD  
       INTEGER iG, jG  
49        INTEGER bi, bj        INTEGER bi, bj
50        INTEGER  I,  J, K        INTEGER i, j, k, localWarnings
51        REAL rad, rD        CHARACTER*(MAX_LEN_MBUF) msgBuf
52    CEOP
53    
54        _BARRIER  C--   Initialise salinity field to the vertical reference profile
55          DO bj = myByLo(myThid), myByHi(myThid)
56        IF ( hydrogSaltFile .EQ. ' ' ) THEN         DO bi = myBxLo(myThid), myBxHi(myThid)
57  C--    Initialise salinity field to the vertical reference profile          DO k=1,Nr
58         DO bj = myByLo(myThid), myByHi(myThid)           DO j=1-Oly,sNy+Oly
59          DO bi = myBxLo(myThid), myBxHi(myThid)            DO i=1-Olx,sNx+Olx
60           DO K=1,Nr             salt(i,j,k,bi,bj) = sRef(k)
           DO J=1,sNy  
            DO I=1,sNx  
             salt(I,J,K,bi,bj) = sRef(K)  
            ENDDO  
61            ENDDO            ENDDO
62           ENDDO           ENDDO
63          ENDDO          ENDDO
64         ENDDO         ENDDO
65        ELSE        ENDDO
66         _BEGIN_MASTER( myThid )  
67         CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )        IF ( hydrogSaltFile .NE. ' ' ) THEN
68         _END_MASTER(myThid)  #ifdef ALLOW_MNC
69            IF ( useMNC.AND.mnc_read_salt ) THEN
70              CALL MNC_FILE_CLOSE_ALL_MATCHING(hydrogSaltFile, myThid)
71              CALL MNC_CW_SET_UDIM(hydrogSaltFile, 1, myThid)
72              CALL MNC_CW_SET_CITER(hydrogSaltFile, 2, -1, -1, -1, myThid)
73              CALL MNC_CW_SET_UDIM(hydrogSaltFile, 1, myThid)
74              CALL MNC_CW_RL_R('D',hydrogSaltFile,0,0,'S',salt, myThid)
75              CALL MNC_FILE_CLOSE_ALL_MATCHING(hydrogSaltFile, myThid)
76            ELSE
77    #endif /*  ALLOW_MNC  */
78              CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )
79    #ifdef ALLOW_MNC
80            ENDIF
81    #endif /*  ALLOW_MNC  */
82            _EXCH_XYZ_RL( salt, myThid )
83        ENDIF        ENDIF
84  C     Set initial tendency terms  
85    C--   Apply mask and test consistency
86          localWarnings=0
87        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
88         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
89          DO K=1,Nr          DO k=1,Nr
90           DO J=1,sNy           IF ( maskIniSalt ) THEN
91            DO I=1,sNx            DO j=1-Oly,sNy+Oly
92             gs   (I,J,K,bi,bj) = 0. _d 0             DO i=1-Olx,sNx+Olx
93             gsNM1(I,J,K,bi,bj) = 0. _d 0              IF (maskC(i,j,k,bi,bj).EQ.0.) salt(i,j,k,bi,bj) = 0.
94               ENDDO
95            ENDDO            ENDDO
96           ENDDO           ENDIF
97             IF ( sRef(k).NE.0. ) THEN
98              DO j=1,sNy
99               DO i=1,sNx
100                IF ( maskC(i,j,k,bi,bj).NE.0.
101         &      .AND. salt(i,j,k,bi,bj).EQ.0. ) THEN
102                  localWarnings=localWarnings+1
103                ENDIF
104               ENDDO
105              ENDDO
106             ENDIF
107          ENDDO          ENDDO
108         ENDDO         ENDDO
109        ENDDO        ENDDO
110  C        IF ( localWarnings.NE.0 ) THEN
111        _EXCH_XYZ_R8(salt  , myThid )         IF ( checkIniSalt ) THEN
112        _EXCH_XYZ_R8(gs , myThid )          WRITE(msgBuf,'(A,I10,A)')
113        _EXCH_XYZ_R8(gsNM1 , myThid )       &   ' INI_SALT: found', localWarnings,
114         &   ' wet grid-pts with salt=0 identically.'
115            CALL PRINT_ERROR( msgBuf , myThid)
116            WRITE(msgBuf,'(A,A)')
117         &  ' If this is intentional, you need to',
118         &  ' set checkIniSalt=.false. in "data", namelist PARM05'
119            CALL PRINT_ERROR( msgBuf , myThid)
120            STOP 'ABNORMAL END: S/R INI_SALT'
121           ELSE
122            WRITE(msgBuf,'(A,I10,A)')
123         &   '** WARNINGS ** INI_SALT: found', localWarnings,
124         &   ' wet grid-pts with salt=0 identically.'
125            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
126         &                      SQUEEZE_RIGHT, myThid )
127           ENDIF
128          ENDIF
129    
130        CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity' , Nr, 1, myThid )        IF (debugMode) THEN
131            CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity',
132         &                         Nr, 1, myThid )
133          ENDIF
134    
135        RETURN        RETURN
136        END        END

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22