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

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

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

revision 1.7 by cnh, Fri Nov 6 22:44:47 1998 UTC revision 1.19 by jmc, Tue Apr 28 18:01:14 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  CStartOfInterface  CBOP
7    C     !ROUTINE: INI_SALT
8    C     !INTERFACE:
9        SUBROUTINE INI_SALT ( myThid )        SUBROUTINE INI_SALT ( myThid )
10  C     /==========================================================\  C     !DESCRIPTION: \bv
11  C     | SUBROUTINE INI_SALT                                      |  C     *==========================================================*
12  C     | o Set model initial salinity field.                      |  C     | SUBROUTINE INI_SALT                                      
13  C     |==========================================================|  C     | o Set model initial salinity field.                      
14  C     | There are several options for setting the initial        |  C     *==========================================================*
15  C     | temperature file                                         |  C     | There are several options for setting the initial        
16  C     |  1. Inline code                                          |  C     | temperature file                                          
17  C     |  2. Vertical profile ( uniform S in X and Y )            |  C     |  1. Inline code                                          
18  C     |  3. Three-dimensional data from a file. For example from |  C     |  2. Vertical profile ( uniform S in X and Y )            
19  C     |     Levitus or from a checkpoint file from a previous    |  C     |  3. Three-dimensional data from a file. For example from  
20  C     |     integration.                                         |  C     |     Levitus or from a checkpoint file from a previous    
21  C     | In addition to setting the salinity field we also        |  C     |     integration.                                          
22  C     | set the initial salinity tendency term here.             |  C     | In addition to setting the salinity field we also        
23  C     \==========================================================/  C     | set the initial salinity tendency term here.              
24    C     *==========================================================*
25    C     \ev
26    
27    C     !USES:
28          IMPLICIT NONE
29  C     === Global variables ===  C     === Global variables ===
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
32  #include "PARAMS.h"  #include "PARAMS.h"
33  #include "GRID.h"  #include "GRID.h"
34  #include "DYNVARS.h"  #include "DYNVARS.h"
35    #ifdef ALLOW_MNC
36    #include "MNC_PARAMS.h"
37    #endif
38    
39    C     !INPUT/OUTPUT PARAMETERS:
40  C     == Routine arguments ==  C     == Routine arguments ==
41  C     myThid -  Number of this instance of INI_SALT  C     myThid -  Number of this instance of INI_SALT
42        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
43    
44    C     !LOCAL VARIABLES:
45  C     == Local variables ==  C     == Local variables ==
 C     iC, jC - Center of domain  
 C     iD, jD - Disitance from domain center.  
 C     rad    - Radius of initial patch  
 C     rD     - Radial displacement of point I,J  
 C     iG, jG - Global coordinate index  
46  C     bi,bj  - Loop counters  C     bi,bj  - Loop counters
47  C     I,J,K  C     I,J,K
       INTEGER iC, jC, iD, jD  
       INTEGER iG, jG  
48        INTEGER bi, bj        INTEGER bi, bj
49        INTEGER  I,  J, K        INTEGER I, J, K, localWarnings
50        REAL rad, rD        CHARACTER*(MAX_LEN_MBUF) msgBuf
51    CEOP
52    
53        _BARRIER  C--   Initialise salinity field to the vertical reference profile
54          DO bj = myByLo(myThid), myByHi(myThid)
55        IF ( hydrogSaltFile .EQ. ' ' ) THEN         DO bi = myBxLo(myThid), myBxHi(myThid)
56  C--    Initialise salinity field to the vertical reference profile          DO K=1,Nr
57         DO bj = myByLo(myThid), myByHi(myThid)           DO J=1-Oly,sNy+Oly
58          DO bi = myBxLo(myThid), myBxHi(myThid)            DO I=1-Olx,sNx+Olx
59           DO K=1,Nr             salt(I,J,K,bi,bj) = sRef(K)
           DO J=1,sNy  
            DO I=1,sNx  
             salt(I,J,K,bi,bj) = sRef(K)  
            ENDDO  
60            ENDDO            ENDDO
61           ENDDO           ENDDO
62          ENDDO          ENDDO
63         ENDDO         ENDDO
64        ELSE        ENDDO
65         _BEGIN_MASTER( myThid )        _BARRIER
66         CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )  
67         _END_MASTER(myThid)        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    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           _EXCH_XYZ_RL(salt  , myThid )
85        ENDIF        ENDIF
86  C     Set initial tendency terms  
87    C     Apply mask and test consistancy
88          localWarnings=0
89        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
90         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
91          DO K=1,Nr          DO K=1,Nr
92           DO J=1,sNy           DO J=1-Oly,sNy+Oly
93            DO I=1,sNx            DO I=1-Olx,sNx+Olx
94             gs   (I,J,K,bi,bj) = 0. _d 0             IF (maskC(I,J,K,bi,bj).EQ.0.) salt(I,J,K,bi,bj) = 0.
            gsNM1(I,J,K,bi,bj) = 0. _d 0  
95            ENDDO            ENDDO
96           ENDDO           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                ENDIF
104               ENDDO
105              ENDDO
106             ENDIF
107          ENDDO          ENDDO
108         ENDDO         ENDDO
109        ENDDO        ENDDO
110  C        IF (localWarnings.NE.0) THEN
111        _EXCH_XYZ_R8(salt  , myThid )         WRITE(msgBuf,'(A,A)')
112        _EXCH_XYZ_R8(gs , myThid )       &  'S/R INI_SALT: salt = 0 identically. If this is intentional',
113        _EXCH_XYZ_R8(gsNM1 , myThid )       &  '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    
118        CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity' , Nr, 1, myThid )        CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity' , Nr, 1, myThid )
119    

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.22