/[MITgcm]/MITgcm_contrib/nesting_sannino/code_nest_merged/ini_salt.F
ViewVC logotype

Contents of /MITgcm_contrib/nesting_sannino/code_nest_merged/ini_salt.F

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


Revision 1.2 - (show annotations) (download)
Tue Nov 24 00:12:22 2009 UTC (16 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +1 -1 lines
FILE REMOVED
not different from model/src version except commented debug print: removed

1 C $Header: /u/gcmpack/MITgcm_contrib/nesting_sannino/code_nest_merged/ini_salt.F,v 1.1 2009/10/21 00:00:27 heimbach Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_SALT
9 C !INTERFACE:
10 SUBROUTINE INI_SALT ( myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE INI_SALT
14 C | o Set model initial salinity field.
15 C *==========================================================*
16 C | There are several options for setting the initial
17 C | temperature file
18 C | 1. Inline code
19 C | 2. Vertical profile ( uniform S in X and Y )
20 C | 3. Three-dimensional data from a file. For example from
21 C | Levitus or from a checkpoint file from a previous
22 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 ===
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #include "GRID.h"
35 #include "DYNVARS.h"
36 #ifdef ALLOW_MNC
37 #include "MNC_PARAMS.h"
38 #endif
39
40 C !INPUT/OUTPUT PARAMETERS:
41 C == Routine arguments ==
42 C myThid :: Number of this instance of INI_SALT
43 INTEGER myThid
44
45 C !LOCAL VARIABLES:
46 C == Local variables ==
47 C bi,bj :: Tile indices
48 C i,j,k :: Loop counters
49 INTEGER bi, bj
50 INTEGER i, j, k, localWarnings
51 CHARACTER*(MAX_LEN_MBUF) msgBuf
52 CEOP
53
54 C-- Initialise salinity field to the vertical reference profile
55 DO bj = myByLo(myThid), myByHi(myThid)
56 DO bi = myBxLo(myThid), myBxHi(myThid)
57 DO k=1,Nr
58 DO j=1-Oly,sNy+Oly
59 DO i=1-Olx,sNx+Olx
60 salt(i,j,k,bi,bj) = sRef(k)
61 ENDDO
62 ENDDO
63 ENDDO
64 ENDDO
65 ENDDO
66
67 IF ( hydrogSaltFile .NE. ' ' ) THEN
68 #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
84
85 cgm( Need to check
86 cph does "-2,0" mean -oLx+1,0?
87 c#ifdef ALLOW_NEST_CHILD
88 c# ifndef ALLOW_USE_MPI
89 c DO I = -2,0
90 c salt(I,:,:,:,:) = salt(1,:,:,:,:)
91 c ENDDO
92 c# endif
93 c#endif
94 cgm)
95
96 C Apply mask and test consistancy
97 localWarnings=0
98 DO bj = myByLo(myThid), myByHi(myThid)
99 DO bi = myBxLo(myThid), myBxHi(myThid)
100 DO k=1,Nr
101 IF ( maskIniSalt ) THEN
102 DO j=1-Oly,sNy+Oly
103 DO i=1-Olx,sNx+Olx
104 IF (maskC(i,j,k,bi,bj).EQ.0.) salt(i,j,k,bi,bj) = 0.
105 ENDDO
106 ENDDO
107 ENDIF
108 IF ( sRef(k).NE.0. ) THEN
109 DO j=1,sNy
110 DO i=1,sNx
111 IF ( maskC(i,j,k,bi,bj).NE.0.
112 & .AND. salt(i,j,k,bi,bj).EQ.0. ) THEN
113 localWarnings=localWarnings+1
114 ENDIF
115 ENDDO
116 ENDDO
117 ENDIF
118 ENDDO
119 ENDDO
120 ENDDO
121 IF ( localWarnings.NE.0 ) THEN
122 IF ( checkIniSalt ) THEN
123 WRITE(msgBuf,'(A,I10,A)')
124 & ' INI_SALT: found', localWarnings,
125 & ' wet grid-pts with salt=0 identically.'
126 CALL PRINT_ERROR( msgBuf , myThid)
127 WRITE(msgBuf,'(A,A)')
128 & ' If this is intentional, you need to',
129 & ' set checkIniSalt=.false. in "data", namelist PARM05'
130 CALL PRINT_ERROR( msgBuf , myThid)
131 STOP 'ABNORMAL END: S/R INI_SALT'
132 ELSE
133 WRITE(msgBuf,'(A,I10,A)')
134 & '** WARNINGS ** INI_SALT: found', localWarnings,
135 & ' wet grid-pts with salt=0 identically.'
136 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
137 & SQUEEZE_RIGHT, myThid )
138 ENDIF
139 ENDIF
140
141 IF (debugMode) THEN
142 CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity',
143 & Nr, 1, myThid )
144 ENDIF
145
146 RETURN
147 END

  ViewVC Help
Powered by ViewVC 1.1.22