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

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

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


Revision 1.24 - (show annotations) (download)
Wed Jun 8 01:27:59 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62z, checkpoint63g, checkpoint64, checkpoint65, checkpoint63, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.23: +3 -2 lines
test debugLevel (instead of debugMode) to print maps (using PLOT_FIELDS call)

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_salt.F,v 1.23 2010/01/18 19:37:35 jmc 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
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE INI_SALT
15 C | o Set model initial salinity field.
16 C *==========================================================*
17 C | There are several options for setting the initial
18 C | temperature file
19 C | 1. Inline code
20 C | 2. Vertical profile ( uniform S in X and Y )
21 C | 3. Three-dimensional data from a file. For example from
22 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 ===
32 #include "SIZE.h"
33 #include "EEPARAMS.h"
34 #include "PARAMS.h"
35 #include "GRID.h"
36 #include "DYNVARS.h"
37 #ifdef ALLOW_MNC
38 #include "MNC_PARAMS.h"
39 #endif
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C == Routine arguments ==
43 C myThid :: Number of this instance of INI_SALT
44 INTEGER myThid
45
46 C !LOCAL VARIABLES:
47 C == Local variables ==
48 C bi,bj :: Tile indices
49 C i,j,k :: Loop counters
50 INTEGER bi, bj
51 INTEGER i, j, k, localWarnings
52 CHARACTER*(MAX_LEN_MBUF) msgBuf
53 CEOP
54
55 C-- Initialise salinity field to the vertical reference profile
56 DO bj = myByLo(myThid), myByHi(myThid)
57 DO bi = myBxLo(myThid), myBxHi(myThid)
58 DO k=1,Nr
59 DO j=1-Oly,sNy+Oly
60 DO i=1-Olx,sNx+Olx
61 salt(i,j,k,bi,bj) = sRef(k)
62 ENDDO
63 ENDDO
64 ENDDO
65 ENDDO
66 ENDDO
67
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)
89 DO bi = myBxLo(myThid), myBxHi(myThid)
90 DO k=1,Nr
91 IF ( maskIniSalt ) THEN
92 DO j=1-Oly,sNy+Oly
93 DO i=1-Olx,sNx+Olx
94 IF (maskC(i,j,k,bi,bj).EQ.0.) salt(i,j,k,bi,bj) = 0.
95 ENDDO
96 ENDDO
97 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
109 ENDDO
110 ENDDO
111 IF ( localWarnings.NE.0 ) THEN
112 IF ( checkIniSalt ) THEN
113 WRITE(msgBuf,'(A,I10,A)')
114 & ' 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 ( debugLevel.GE.debLevC ) THEN
132 CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity',
133 & Nr, 1, myThid )
134 ENDIF
135
136 RETURN
137 END

  ViewVC Help
Powered by ViewVC 1.1.22