/[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.2 by cnh, Fri Apr 24 02:05:41 1998 UTC revision 1.13 by adcroft, Tue May 29 14:01:37 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  CStartOfInterface  CStartOfInterface
7        SUBROUTINE INI_SALT ( myThid )        SUBROUTINE INI_SALT ( myThid )
# Line 18  C     |     integration. Line 19  C     |     integration.
19  C     | In addition to setting the salinity field we also        |  C     | In addition to setting the salinity field we also        |
20  C     | set the initial salinity tendency term here.             |  C     | set the initial salinity tendency term here.             |
21  C     \==========================================================/  C     \==========================================================/
22          IMPLICIT NONE
23    
24  C     === Global variables ===  C     === Global variables ===
25  #include "SIZE.h"  #include "SIZE.h"
# Line 32  C     myThid -  Number of this instance Line 34  C     myThid -  Number of this instance
34  CEndOfInterface  CEndOfInterface
35    
36  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  
37  C     bi,bj  - Loop counters  C     bi,bj  - Loop counters
38  C     I,J,K  C     I,J,K
       INTEGER iC, jC, iD, jD  
       INTEGER iG, jG  
39        INTEGER bi, bj        INTEGER bi, bj
40        INTEGER  I,  J, K        INTEGER  I,  J, K, localWarnings
41        REAL rad, rD        CHARACTER*(MAX_LEN_MBUF) msgBuf
42    
43  C--   Initialise salinity field to the vertical reference profile  C--   Initialise salinity field to the vertical reference profile
44        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
45         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
46          DO K=1,Nz          DO K=1,Nr
47           DO J=1,sNy           DO J=1-Oly,sNy+Oly
48            DO I=1,sNx            DO I=1-Olx,sNx+Olx
49             salt(I,J,K,bi,bj) = sRef(K)             salt(I,J,K,bi,bj) = sRef(K)
50            ENDDO            ENDDO
51           ENDDO           ENDDO
52          ENDDO          ENDDO
53         ENDDO         ENDDO
54        ENDDO        ENDDO
55  C     Set initial tendency terms  
56          IF ( hydrogSaltFile .NE. ' ' ) THEN
57           _BEGIN_MASTER( myThid )
58           CALL READ_FLD_XYZ_RL( hydrogSaltFile, ' ', salt, 0, myThid )
59           _END_MASTER(myThid)
60           _EXCH_XYZ_R8(salt  , myThid )
61          ENDIF
62    
63    C     Apply mask and test consistancy
64          localWarnings=0
65        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
66         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
67          DO K=1,Nz          DO K=1,Nr
68           DO J=1,sNy           DO J=1,sNy
69            DO I=1,sNx            DO I=1,sNx
70             gs   (I,J,K,bi,bj) = 0. _d 0             IF (hFacC(I,J,K,bi,bj).EQ.0) salt(I,J,K,bi,bj) = 0.
71             gsNM1(I,J,K,bi,bj) = 0. _d 0             IF (hFacC(I,J,K,bi,bj).NE.0.AND.salt(I,J,K,bi,bj).EQ.0.
72         &      .AND. sRef(k).NE.0.) THEN
73                 localWarnings=localWarnings+1
74                ENDIF
75            ENDDO            ENDDO
76           ENDDO           ENDDO
77          ENDDO          ENDDO
78         ENDDO         ENDDO
79        ENDDO        ENDDO
80  C        IF (localWarnings.NE.0) THEN
81        _EXCH_XYZ_R8(salt  , myThid )         WRITE(msgBuf,'(A,A)')
82        _EXCH_XYZ_R8(gs , myThid )       &  'S/R INI_SALT: salt = 0 identically. If this is intentional',
83        _EXCH_XYZ_R8(gsNM1 , myThid )       &  'you will need to edit ini_salt.F to avoid this safety check'
84           CALL PRINT_ERROR( msgBuf , myThid)
85           STOP 'ABNORMAL END: S/R INI_SALT'
86          ENDIF
87    
88          CALL PLOT_FIELD_XYZRL( salt, 'Initial Salinity' , Nr, 1, myThid )
89    
90        RETURN        RETURN
91        END        END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22