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

Legend:
Removed from v.1.1.1.1  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22