New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
domzgr_s.h90 in trunk/NEMO/OPA_SRC/DOM – NEMO

source: trunk/NEMO/OPA_SRC/DOM/domzgr_s.h90 @ 384

Last change on this file since 384 was 253, checked in by opalod, 19 years ago

nemo_v1_update_001 : Add the 1D configuration possibility

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.7 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                     ***  domzgr.s.h90  ***
3   !!----------------------------------------------------------------------
4   !!----------------------------------------------------------------------
5   !!  OPA 9.0 , LOCEAN-IPSL (2005)
6   !! $Header$
7   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
8   !!----------------------------------------------------------------------
9
10#if defined key_s_coord
11   !!----------------------------------------------------------------------
12   !!   'key_s_coord' :                                        s-coordinate
13   !!----------------------------------------------------------------------
14
15   SUBROUTINE zgr_s
16      !!----------------------------------------------------------------------
17      !!                  ***  ROUTINE zgr_s  ***
18      !!                     
19      !! ** Purpose :   define the s-coordinate system
20      !!
21      !! ** Method  :   s-coordinate
22      !!         The depth of model levels is defined as the product of an
23      !!      analytical function by the local bathymetry, while the vertical
24      !!      scale factors are defined as the product of the first derivative
25      !!      of the analytical function by the bathymetry.
26      !!      (this solution save memory as depth and scale factors are not
27      !!      3d fields)
28      !!          - Read bathymetry (in meters) at t-point and compute the
29      !!         bathymetry at u-, v-, and f-points.
30      !!            hbatu = mi( hbatt )
31      !!            hbatv = mj( hbatt )
32      !!            hbatf = mi( mj( hbatt ) )
33      !!          - Compute gsigt, gsigw, esigt, esigw from an analytical
34      !!         function and its derivative given as statement function.
35      !!            gsigt(k) = fssig (k+0.5)
36      !!            gsigw(k) = fssig (k    )
37      !!            esigt(k) = fsdsig(k+0.5)
38      !!            esigw(k) = fsdsig(k    )
39      !!      This routine is given as an example, it must be modified
40      !!      following the user s desiderata. nevertheless, the output as
41      !!      well as the way to compute the model levels and scale factors
42      !!      must be respected in order to insure second order a!!uracy
43      !!      schemes.
44      !!
45      !! Reference :
46      !!      Madec, Lott, Delecluse and Crepon, 1996. JPO, 26, 1393-1408.
47      !!
48      !! History :
49      !!        !  95-12  (G. Madec)  Original code : s vertical coordinate
50      !!        !  97-07  (G. Madec)  lbc_lnk call
51      !!        !  97-04  (J.-O. Beismann)
52      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
53      !!----------------------------------------------------------------------
54      !! * Local declarations
55      INTEGER  ::   in
56      INTEGER  ::   ji, jj, jk
57      REAL(wp) ::   fssig, fsdsig, pfkk
58      REAL(wp) ::   zh0, zdz1, zdzn, zd, za, zb, zc, zdepmi
59
60      !!----------------------------------------------------------------------
61      !!  OPA 8.5, LODYC-IPSL (2002)
62      !!----------------------------------------------------------------------
63
64      ! a. Sigma stretching coefficient
65      !      hyperbolic stretching sigma= za(in-jk)^3+zb(in-jk)^2+zc(in-jk)+zd
66      !      hyperbolic stretching sigma= za(jk)^3+zb(jk)^2+zc(jk)+zd
67      !  calculate stretching coefficients (to ensure
68      !        ss(sigma) =1 at sigma=1,  and -1 at sigma=-1)
69      !        sigma =1 at the surface (k=1) and  =-1 at the bottom (k=jpk)
70      !   the only free parameters are the depths of the  first level
71      !   dz1 and of the last level(zdzn) in meters (given as a positive
72      !   quantity).
73     
74      fssig(pfkk) =-0.5* ( ( ( za*(pfkk-1.) + zb ) * (pfkk-1.) + zc ) * (pfkk-1.) + zd -1. )
75
76      ! b. Vertical derivative of sigma stretching coefficient
77     
78      fsdsig(pfkk)= 0.5*( ( 3.*za*(pfkk-1.) + 2.*zb )* (pfkk-1.) + zc )
79     
80      ! ------------------ stretching polynomial ------------------------
81     
82      ! SPEM coefficients
83      ! spem opa: kopa= jpk-kspem
84      !        pfkk =in-jk (spem) <==> pfkk=in-jk-jpk=-jk-1  (opa)
85
86      zh0  = 5500.
87      zdz1 = 800.
88      zdzn = 17.5
89      in   = 19
90
91      IF(lwp) THEN
92         WRITE(numout,*) ' stretching with a third order polynamial'
93         WRITE(numout,*) ' h0 = ',zh0
94         WRITE(numout,*) ' at ',zh0,'  dz(1)= z(1)-z(0)   = ',zdz1
95         WRITE(numout,*) '             dz(n)= z(n)-z(n-1) = ',zdzn
96      ENDIF
97
98      za =     - 2.*(zdz1+zdzn)/zh0/float(in-1)/float(in-2)   &
99                + 4./float(in)/float(in-1)/float(in-2)
100
101      zb =     - 6./float(in-1)/float(in-2)   &
102                + 2.*(zdz1*float(in+1)+ zdzn*float(2*in-1))   &
103                /zh0/float(in-2)/float(in-1)
104
105      zc =     -2.*zdzn*float(in)/zh0/float(in-2)   &
106                -2.*zdz1*float(in)/zh0/float(in-1)/float(in-2)   &
107                +(6.* float(in) - 4.)/float(in)/float(in-1)/float(in-2)
108
109      zd =     1.
110
111      !!----------------------------------------------------------------------
112      !!  OPA 8.5, LODYC-IPSL (2002)
113      !!----------------------------------------------------------------------
114
115
116      ! 1. Lecture and computation of hbat fields
117      ! -----------------------------------------
118
119      ! 1.1 Read hbatt (in meters)
120      ! 1.2 Set the hbatt to negative value   ???
121
122      hbatt(:,:) = - bathy(:,:)
123
124
125      ! 1.3 Set a minimum depth  (zdepmi)
126
127      zdepmi = -50.
128      IF( zdepmi >= 0. ) THEN
129         IF(lwp) WRITE(numout,*)'domzgr: the minimum depth must be < 0'
130         STOP 'domzgr'
131      ENDIF
132      DO jj = 1, jpj
133         DO ji = 1, jpi
134            hbatt(ji,jj) = MIN( hbatt(ji,jj), zdepmi )
135            hbatu(ji,jj) = zdepmi
136            hbatv(ji,jj) = zdepmi
137            hbatf(ji,jj) = zdepmi
138         END DO
139      END DO
140
141      CALL lbc_lnk( hbatt, 'T', 1. )
142
143      IF(lwp) THEN
144         WRITE(numout,*)
145         WRITE(numout,*) ' domzgr: minimum depth set to : ',zdepmi
146         WRITE(numout,*)
147      ENDIF
148
149      ! 1.4 Control print
150
151      IF(lwp) THEN
152         WRITE(numout,*)
153         WRITE(numout,*) ' domzgr: hbatt field; ocean depth in meters'
154         WRITE(numout,*)
155         CALL prihre(hbatt(1,1),jpi,jpj,1,jpi,1,1,jpj,1,0.,numout)
156      ENDIF
157
158      ! 1.5 Compute hbat fields at u-, v-, f-points
159
160      DO jj = 1, jpjm1
161        DO ji = 1, jpim1
162           hbatu(ji,jj)= 0.5 *( hbatt(ji  ,jj)+hbatt(ji+1,jj  ) ) * umask(ji,jj,1)
163           hbatv(ji,jj)= 0.5 *( hbatt(ji  ,jj)+hbatt(ji  ,jj+1) ) * vmask(ji,jj,1)
164           hbatf(ji,jj)= 0.25*( hbatt(ji  ,jj)+hbatt(ji  ,jj+1)   &
165                               +hbatt(ji+1,jj)+hbatt(ji+1,jj+1) ) * fmask(ji,jj,1)
166        END DO
167      END DO
168
169      CALL lbc_lnk( hbatu, 'U', 1. )
170      CALL lbc_lnk( hbatv, 'V', 1. )
171      CALL lbc_lnk( hbatf, 'F', 1. )
172
173
174      ! 2. Computation of gsig and esig fields
175      ! --------------------------------------
176
177      ! 2.1 Coefficients for model level depth at w- and t-levels
178
179      DO jk = 1, jpk
180         gsigw(jk) = -fssig ( float(jk)    )
181         gsigt(jk) = -fssig ( float(jk)+0.5)
182      END DO
183
184      ! 2.2 Coefficients for vertical scale factors at w-, t- levels
185
186      DO jk = 1, jpk
187         esigw(jk)=fsdsig( float(jk)    )
188         esigt(jk)=fsdsig( float(jk)+0.5)
189      END DO
190
191      ! 2.3 Coefficients for vertical depth as the sum of e3w scale factors
192
193      gsi3w(1) = 0.5 * esigw(1)
194      DO jk = 2, jpk
195        gsi3w(jk) = gsi3w(jk-1)+ esigw(jk)
196      END DO
197
198      ! ===========
199      ! Zoom domain
200      ! ===========
201
202      IF( lzoom )   CALL zgr_bat_zoom
203
204      ! 2.4 Control print
205
206      IF(lwp) THEN
207         WRITE(numout,*)
208         WRITE(numout,*) ' domzgr: vertical coefficients for model level'
209         WRITE(numout,9400)
210         WRITE(numout,9410) (jk,gsigt(jk),gsigw(jk),esigt(jk),esigw(jk),gsi3w(jk),jk=1,jpk)
211      ENDIF
212 9400 FORMAT(9x,' level   gsigt    gsigw    esigt    esigw    gsi3w')
213 9410 FORMAT(10x,i4,5f9.2)
214
215      IF(lwp) THEN
216         WRITE(numout,*)
217         WRITE(numout,*) ' domzgr: vertical coordinates : point (10,10,k)'
218         WRITE(numout,*) ' ~~~~~~  --------------------'
219         WRITE(numout,9420)
220         WRITE(numout,9430) (jk,fsdept(10,10,jk),fsdepw(10,10,jk),     &
221                             fse3t (10,10,jk),fse3w (10,10,jk),jk=1,jpk)
222      ENDIF
223
224 9420 FORMAT(9x,' level   gdept    gdepw    gde3w     e3t      e3w  ')
225 9430 FORMAT(10x,i4,4f9.2)
226
227      DO jk = 1, jpk
228         DO jj = 1, jpj
229            DO ji = 1, jpi
230               IF( fse3w(ji,jj,jk) <= 0. .OR. fse3t(ji,jj,jk) <= 0. ) THEN
231                  IF(lwp) THEN
232                     WRITE(numout,*)
233                     WRITE(numout,*) ' e r r o r :         e3w or e3t =< 0 '
234                     WRITE(numout,*) ' =========           --------------- '
235                     WRITE(numout,*)
236                     WRITE(numout,*) '             point (i,j,k)= ',ji,jj,jk
237                     WRITE(numout,*)
238                  ENDIF
239                  STOP 'domzgr'
240               ENDIF
241               IF( fsdepw(ji,jj,jk) < 0. .OR. fsdept(ji,jj,jk) < 0. ) THEN
242                  IF(lwp) THEN
243                     WRITE(numout,*)
244                     WRITE(numout,*) ' e r r o r :      gdepw or gdept < 0 '
245                     WRITE(numout,*) ' =========        ------------------ '
246                     WRITE(numout,*)
247                     WRITE(numout,*) '             point (i,j,k)= ',ji,jj,jk
248                     WRITE(numout,*)
249                  ENDIF
250                  STOP 'domzgr'
251               ENDIF
252            END DO
253         END DO
254      END DO
255
256   END SUBROUTINE zgr_s
257
258#else
259   !!----------------------------------------------------------------------
260   !!   Default option :                                      Empty routine
261   !!----------------------------------------------------------------------
262   SUBROUTINE zgr_s
263   END SUBROUTINE zgr_s
264#endif
Note: See TracBrowser for help on using the repository browser.