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

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

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


Revision 1.18 - (hide annotations) (download)
Sun Nov 5 18:36:06 2006 UTC (17 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint60, checkpoint61, checkpoint58w_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58v_post, checkpoint61f, checkpoint58x_post, checkpoint59j, checkpoint61e, checkpoint58u_post, checkpoint58s_post, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.17: +20 -4 lines
add ability to read bathy, salt, and theta using MNC (off by def)
  -- and this can be readily extended to most of the other files
  in PARM05 of the main "data" namelist file

1 edhill 1.18 C $Header: /u/gcmpack/MITgcm/model/src/ini_salt.F,v 1.17 2005/11/08 23:01:10 cnh Exp $
2 adcroft 1.13 C $Name: $
3 cnh 1.1
4 cnh 1.7 #include "CPP_OPTIONS.h"
5 cnh 1.1
6 cnh 1.14 CBOP
7     C !ROUTINE: INI_SALT
8     C !INTERFACE:
9 cnh 1.1 SUBROUTINE INI_SALT ( myThid )
10 cnh 1.14 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.9 IMPLICIT NONE
29 cnh 1.1 C === Global variables ===
30     #include "SIZE.h"
31     #include "EEPARAMS.h"
32     #include "PARAMS.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35 edhill 1.18 #ifdef ALLOW_MNC
36     #include "MNC_PARAMS.h"
37     #endif
38 cnh 1.1
39 cnh 1.14 C !INPUT/OUTPUT PARAMETERS:
40 cnh 1.1 C == Routine arguments ==
41     C myThid - Number of this instance of INI_SALT
42     INTEGER myThid
43    
44 cnh 1.14 C !LOCAL VARIABLES:
45 cnh 1.1 C == Local variables ==
46     C bi,bj - Loop counters
47     C I,J,K
48     INTEGER bi, bj
49 jmc 1.15 INTEGER I, J, K, localWarnings
50 adcroft 1.13 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 cnh 1.14 CEOP
52 cnh 1.1
53 adcroft 1.13 C-- Initialise salinity field to the vertical reference profile
54     DO bj = myByLo(myThid), myByHi(myThid)
55     DO bi = myBxLo(myThid), myBxHi(myThid)
56     DO K=1,Nr
57     DO J=1-Oly,sNy+Oly
58     DO I=1-Olx,sNx+Olx
59     salt(I,J,K,bi,bj) = sRef(K)
60 cnh 1.1 ENDDO
61     ENDDO
62     ENDDO
63     ENDDO
64 adcroft 1.13 ENDDO
65 cnh 1.16 _BARRIER
66 adcroft 1.13
67     IF ( hydrogSaltFile .NE. ' ' ) THEN
68 edhill 1.18 #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     C _BEGIN_MASTER( myThid )
79     CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )
80     C _END_MASTER(myThid)
81     #ifdef ALLOW_MNC
82     ENDIF
83     #endif /* ALLOW_MNC */
84 adcroft 1.13 _EXCH_XYZ_R8(salt , myThid )
85 cnh 1.3 ENDIF
86 adcroft 1.13
87     C Apply mask and test consistancy
88     localWarnings=0
89 cnh 1.1 DO bj = myByLo(myThid), myByHi(myThid)
90     DO bi = myBxLo(myThid), myBxHi(myThid)
91 cnh 1.6 DO K=1,Nr
92 jmc 1.15 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     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 adcroft 1.13 ENDIF
104 jmc 1.15 ENDDO
105 cnh 1.1 ENDDO
106 jmc 1.15 ENDIF
107 cnh 1.1 ENDDO
108     ENDDO
109     ENDDO
110 adcroft 1.13 IF (localWarnings.NE.0) THEN
111     WRITE(msgBuf,'(A,A)')
112     & 'S/R INI_SALT: salt = 0 identically. If this is intentional',
113     & 'you will need to edit ini_salt.F to avoid this safety check'
114     CALL PRINT_ERROR( msgBuf , myThid)
115     STOP 'ABNORMAL END: S/R INI_SALT'
116     ENDIF
117 cnh 1.5
118 cnh 1.6 CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity' , Nr, 1, myThid )
119 cnh 1.5
120 cnh 1.1 RETURN
121     END

  ViewVC Help
Powered by ViewVC 1.1.22