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

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

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


Revision 1.3 - (hide annotations) (download)
Mon Jan 18 19:42:10 2010 UTC (14 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint64, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint64q, checkpoint64p, checkpoint64r, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.2: +89 -50 lines
- closer to standard version (from model/src)
- add "_d 0" (more robust when RS is real*4)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/model/src/ini_salt.F,v 1.22 2009/10/15 01:06:51 jmc Exp $
2 adcroft 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6 jmc 1.3 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 adcroft 1.1 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 jmc 1.3 C !INPUT/OUTPUT PARAMETERS:
37 adcroft 1.1 C == Routine arguments ==
38 jmc 1.3 C myThid :: Number of this instance of INI_SALT
39 adcroft 1.1 INTEGER myThid
40    
41 jmc 1.3 C !LOCAL VARIABLES:
42 adcroft 1.1 C == Local variables ==
43 jmc 1.3 C bi,bj :: Tile indices
44     C i,j,k :: Loop counters
45     C rD :: Radial displacement of point i,j
46 adcroft 1.1 INTEGER bi, bj
47 jmc 1.3 INTEGER i, j, k, localWarnings
48     _RL rD
49 adcroft 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 jmc 1.3 CEOP
51 adcroft 1.1
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 jmc 1.3 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 adcroft 1.1 ENDDO
71     ENDDO
72 jmc 1.3 C=== Set-up specific modification ends here ===
73 adcroft 1.1 ENDDO
74     ENDDO
75     ENDDO
76    
77     IF ( hydrogSaltFile .NE. ' ' ) THEN
78 jmc 1.3 CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )
79     _EXCH_XYZ_RL( salt, myThid )
80 adcroft 1.1 ENDIF
81    
82 jmc 1.3 C-- Apply mask and test consistency
83 adcroft 1.1 localWarnings=0
84     DO bj = myByLo(myThid), myByHi(myThid)
85     DO bi = myBxLo(myThid), myBxHi(myThid)
86 jmc 1.3 DO k=1,Nr
87     IF ( maskIniSalt ) THEN
88     DO j=1-Oly,sNy+Oly
89     DO i=1-Olx,sNx+Olx
90     IF (maskC(i,j,k,bi,bj).EQ.0.) salt(i,j,k,bi,bj) = 0.
91     ENDDO
92     ENDDO
93     ENDIF
94     IF ( sRef(k).NE.0. ) THEN
95     DO j=1,sNy
96     DO i=1,sNx
97     IF ( maskC(i,j,k,bi,bj).NE.0.
98     & .AND. salt(i,j,k,bi,bj).EQ.0. ) THEN
99     localWarnings=localWarnings+1
100 adcroft 1.1 ENDIF
101 jmc 1.3 ENDDO
102 adcroft 1.1 ENDDO
103 jmc 1.3 ENDIF
104 adcroft 1.1 ENDDO
105     ENDDO
106     ENDDO
107 jmc 1.3 IF ( localWarnings.NE.0 ) THEN
108     IF ( checkIniSalt ) THEN
109     WRITE(msgBuf,'(A,I10,A)')
110     & ' INI_SALT: found', localWarnings,
111     & ' wet grid-pts with salt=0 identically.'
112     CALL PRINT_ERROR( msgBuf , myThid)
113     WRITE(msgBuf,'(A,A)')
114     & ' If this is intentional, you need to',
115     & ' set checkIniSalt=.false. in "data", namelist PARM05'
116     CALL PRINT_ERROR( msgBuf , myThid)
117     STOP 'ABNORMAL END: S/R INI_SALT'
118     ELSE
119     WRITE(msgBuf,'(A,I10,A)')
120     & '** WARNINGS ** INI_SALT: found', localWarnings,
121     & ' wet grid-pts with salt=0 identically.'
122     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
123     & SQUEEZE_RIGHT, myThid )
124     ENDIF
125 adcroft 1.1 ENDIF
126    
127 jmc 1.3 IF (debugMode) THEN
128     CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity',
129     & Nr, 1, myThid )
130     ENDIF
131 adcroft 1.1
132     RETURN
133     END

  ViewVC Help
Powered by ViewVC 1.1.22