/[MITgcm]/MITgcm/verification/advect_xy/code/ini_salt.F
ViewVC logotype

Contents of /MITgcm/verification/advect_xy/code/ini_salt.F

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


Revision 1.4 - (show annotations) (download)
Mon Dec 16 18:53:06 2013 UTC (10 years, 5 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, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64s, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, HEAD
Changes since 1.3: +5 -2 lines
add missing EXCH call (similar to customized ini_theta.F here).

1 C $Header: /u/gcmpack/MITgcm/verification/advect_xy/code/ini_salt.F,v 1.3 2010/01/18 19:42:10 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INI_SALT
8 C !INTERFACE:
9 SUBROUTINE INI_SALT( myThid )
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE INI_SALT
13 C | o Set model initial salinity field.
14 C *==========================================================*
15 C | There are several options for setting the initial
16 C | temperature file
17 C | 1. Inline code
18 C | 2. Vertical profile ( uniform S in X and Y )
19 C | 3. Three-dimensional data from a file. For example from
20 C | Levitus or from a checkpoint file from a previous
21 C | integration.
22 C | In addition to setting the salinity field we also
23 C | set the initial salinity tendency term here.
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29 C === Global variables ===
30 #include "SIZE.h"
31 #include "EEPARAMS.h"
32 #include "PARAMS.h"
33 #include "GRID.h"
34 #include "DYNVARS.h"
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C == Routine arguments ==
38 C myThid :: Number of this instance of INI_SALT
39 INTEGER myThid
40
41 C !LOCAL VARIABLES:
42 C == Local variables ==
43 C bi,bj :: Tile indices
44 C i,j,k :: Loop counters
45 C rD :: Radial displacement of point i,j
46 INTEGER bi, bj
47 INTEGER i, j, k, localWarnings
48 _RL rD
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 CEOP
51
52 C-- Initialise salinity field to the vertical reference profile
53 DO bj = myByLo(myThid), myByHi(myThid)
54 DO bi = myBxLo(myThid), myBxHi(myThid)
55 DO k=1,Nr
56 DO j=1-Oly,sNy+Oly
57 DO i=1-Olx,sNx+Olx
58 salt(i,j,k,bi,bj) = sRef(k)
59 ENDDO
60 ENDDO
61 C=== Set-up specific modification starts here ===
62 C-- Initialise salinity field to a circular patch.
63 DO j=1-Oly,sNy+Oly
64 DO i=1-Olx,sNx+Olx
65 rD = SQRT( ( xC(i,j,bi,bj) - 40. _d 3 )**2
66 & +( yC(i,j,bi,bj) - 40. _d 3 )**2
67 & +( rC(k) + 50. _d 3 )**2
68 & )
69 IF ( rD.LE.60. _d 3 ) salt(i,j,k,bi,bj) = sRef(k)+1. _d 0
70 ENDDO
71 ENDDO
72 C=== Set-up specific modification ends here ===
73 ENDDO
74 ENDDO
75 ENDDO
76 C=== Set-up specific modification starts here ===
77 _EXCH_XYZ_RL( salt, myThid )
78 C=== Set-up specific modification ends here ===
79
80 IF ( hydrogSaltFile .NE. ' ' ) THEN
81 CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )
82 _EXCH_XYZ_RL( salt, myThid )
83 ENDIF
84
85 C-- Apply mask and test consistency
86 localWarnings=0
87 DO bj = myByLo(myThid), myByHi(myThid)
88 DO bi = myBxLo(myThid), myBxHi(myThid)
89 DO k=1,Nr
90 IF ( maskIniSalt ) THEN
91 DO j=1-Oly,sNy+Oly
92 DO i=1-Olx,sNx+Olx
93 IF (maskC(i,j,k,bi,bj).EQ.0.) salt(i,j,k,bi,bj) = 0.
94 ENDDO
95 ENDDO
96 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
108 ENDDO
109 ENDDO
110 IF ( localWarnings.NE.0 ) THEN
111 IF ( checkIniSalt ) THEN
112 WRITE(msgBuf,'(A,I10,A)')
113 & ' 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 IF ( debugLevel.GE.debLevC ) THEN
131 CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity',
132 & Nr, 1, myThid )
133 ENDIF
134
135 RETURN
136 END

  ViewVC Help
Powered by ViewVC 1.1.22