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.
sbcana.F90 in tags/nemo_v3_2/nemo_v3_2/NEMO/OPA_SRC/SBC – NEMO

source: tags/nemo_v3_2/nemo_v3_2/NEMO/OPA_SRC/SBC/sbcana.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

File size: 15.6 KB
Line 
1MODULE sbcana
2   !!======================================================================
3   !!                       ***  MODULE  sbcana  ***
4   !! Ocean forcing:  analytical momentum, heat and freshwater forcings
5   !!=====================================================================
6   !! History :  3.0   ! 2006-06  (G. Madec)  Original code
7   !!            3.2   ! 2009-07  (G. Madec)  Style only
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sbc_ana  : set an analytical ocean forcing
12   !!   sbc_gyre : set the GYRE configuration analytical forcing
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE sbc_oce         ! Surface boundary condition: ocean fields
17   USE phycst          ! physical constants
18   USE in_out_manager  ! I/O manager
19   USE lib_mpp         ! distribued memory computing library
20   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   sbc_ana    ! routine called in sbcmod module
26   PUBLIC   sbc_gyre   ! routine called in sbcmod module
27
28   !                               !!* Namelist namsbc_ana *
29   INTEGER  ::   nn_tau000 = 1      ! nb of time-step during which the surface stress
30   !                                ! increase from 0 to its nominal value
31   REAL(wp) ::   rn_utau0  = 0.e0   ! constant wind stress value in i-direction
32   REAL(wp) ::   rn_vtau0  = 0.e0   ! constant wind stress value in j-direction
33   REAL(wp) ::   rn_qns0   = 0.e0   ! non solar heat flux
34   REAL(wp) ::   rn_qsr0   = 0.e0   !     solar heat flux
35   REAL(wp) ::   rn_emp0   = 0.e0   ! net freshwater flux
36   
37   !! * Substitutions
38#  include "domzgr_substitute.h90"
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
42   !! $Id: sbcana.F90 1732 2009-11-16 15:15:24Z smasson $
43   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE sbc_ana( kt )
49      !!---------------------------------------------------------------------
50      !!                    ***  ROUTINE sbc_ana ***
51      !!             
52      !! ** Purpose :   provide at each time-step the ocean surface boundary
53      !!              condition, i.e. the momentum, heat and freshwater fluxes.
54      !!
55      !! ** Method  :   Constant and uniform surface forcing specified from
56      !!              namsbc_ana namelist parameters. All the fluxes are time
57      !!              independant except the stresses which increase from zero
58      !!              during the first nn_tau000 time-step
59      !!                CAUTION : never mask the surface stress field !
60      !!
61      !! ** Action  : - set the ocean surface boundary condition, i.e. 
62      !!                   utau, vtau, taum, wndm, qns, qsr, emp, emps
63      !!----------------------------------------------------------------------
64      INTEGER, INTENT(in) ::   kt       ! ocean time step
65      !!
66      REAL(wp)            ::   zfacto                ! local scalar
67      REAL(wp)            ::   zrhoa  = 1.22         ! Air density kg/m3
68      REAL(wp)            ::   zcdrag = 1.5e-3       ! drag coefficient
69      REAL(wp)            ::   ztx, zty, zmod, zcoef ! temporary variables
70      !!
71      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0
72      !!---------------------------------------------------------------------
73      !
74      IF( kt == nit000 ) THEN
75         !
76         REWIND ( numnam )                   ! Read Namelist namsbc : surface fluxes
77         READ   ( numnam, namsbc_ana )
78         !
79         IF(lwp) WRITE(numout,*)' '
80         IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist'
81         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
82         IF(lwp) WRITE(numout,*)'              spin up of the stress  nn_tau000 = ', nn_tau000, ' time-steps'
83         IF(lwp) WRITE(numout,*)'              constant i-stress      rn_utau0  = ', rn_utau0 , ' N/m2'
84         IF(lwp) WRITE(numout,*)'              constant j-stress      rn_vtau0  = ', rn_vtau0 , ' N/m2'
85         IF(lwp) WRITE(numout,*)'              non solar heat flux    rn_qns0   = ', rn_qns0  , ' W/m2'
86         IF(lwp) WRITE(numout,*)'              solar heat flux        rn_qsr0   = ', rn_qsr0  , ' W/m2'
87         IF(lwp) WRITE(numout,*)'              net heat flux          rn_emp0   = ', rn_emp0  , ' Kg/m2/s'
88         !
89         nn_tau000 = MAX( nn_tau000, 1 )   ! must be >= 1
90         qns   (:,:) = rn_qns0
91         qsr   (:,:) = rn_qsr0
92         emp   (:,:) = rn_emp0
93         emps  (:,:) = rn_emp0
94         !
95      ENDIF
96   
97      ! Increase the surface stress to its nominal value during the first nn_tau000 time-steps
98      IF( kt <= nn_tau000 ) THEN
99         zfacto = 0.5 * (  1. - COS( rpi * FLOAT( kt ) / FLOAT( nn_tau000 ) )  )
100         zcoef = 1. / ( zrhoa * zcdrag ) 
101         ztx = zfacto * rn_utau0
102         zty = zfacto * rn_vtau0
103         zmod = SQRT( ztx * ztx + zty * zty )
104         utau(:,:) = ztx
105         vtau(:,:) = zty
106         taum(:,:) = zmod
107         zmod = SQRT( zmod * zcoef )
108         wndm(:,:) = zmod
109      ENDIF
110      !
111   END SUBROUTINE sbc_ana
112
113
114   SUBROUTINE sbc_gyre( kt )
115      !!---------------------------------------------------------------------
116      !!                    ***  ROUTINE sbc_ana ***
117      !!             
118      !! ** Purpose :   provide at each time-step the GYRE surface boundary
119      !!              condition, i.e. the momentum, heat and freshwater fluxes.
120      !!
121      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
122      !!                CAUTION : never mask the surface stress field !
123      !!
124      !! ** Action  : - set the ocean surface boundary condition, i.e.   
125      !!                   utau, vtau, taum, wndm, qns, qsr, emp, emps
126      !!
127      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
128      !!----------------------------------------------------------------------
129      INTEGER, INTENT(in) ::   kt          ! ocean time step
130      !!
131      INTEGER  ::   ji, jj                 ! dummy loop indices
132      INTEGER  ::   zyear0                 ! initial year
133      INTEGER  ::   zmonth0                ! initial month
134      INTEGER  ::   zday0                  ! initial day
135      INTEGER  ::   zday_year0             ! initial day since january 1st
136      REAL(wp) ::   ztau     , ztau_sais   ! wind intensity and of the seasonal cycle
137      REAL(wp) ::   ztime                  ! time in hour
138      REAL(wp) ::   ztimemax , ztimemin    ! 21th June, and 21th decem. if date0 = 1st january
139      REAL(wp) ::   ztimemax1, ztimemin1   ! 21th June, and 21th decem. if date0 = 1st january
140      REAL(wp) ::   ztimemax2, ztimemin2   ! 21th June, and 21th decem. if date0 = 1st january
141      REAL(wp) ::   ztaun                  ! intensity
142      REAL(wp) ::   zemp_s, zemp_n, zemp_sais, ztstar
143      REAL(wp) ::   zcos_sais1, zcos_sais2, ztrp, zconv, t_star
144      REAL(wp) ::   zsumemp, zsurf
145      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
146      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
147      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
148      REAL(wp) ::   zyydd                 ! number of days in one year
149      !!---------------------------------------------------------------------
150      zyydd = REAL(nyear_len(1),wp)
151
152      ! ---------------------------- !
153      !  heat and freshwater fluxes  !
154      ! ---------------------------- !
155      !same temperature, E-P as in HAZELEGER 2000
156
157      zyear0     =   ndate0 / 10000                             ! initial year
158      zmonth0    = ( ndate0 - zyear0 * 10000 ) / 100            ! initial month
159      zday0      =   ndate0 - zyear0 * 10000 - zmonth0 * 100    ! initial day betwen 1 and 30
160      zday_year0 = ( zmonth0 - 1 ) * 30.+zday0                  ! initial day betwen 1 and 360
161
162      ! current day (in hours) since january the 1st of the current year
163      ztime = REAL( kt ) * rdt / (rmmss * rhhmm)   &       !  total incrementation (in hours)
164         &      - (nyear  - 1) * rjjhh * zyydd             !  minus years since beginning of experiment (in hours)
165
166      ztimemax1 = ((5.*30.)+21.)* 24.                      ! 21th june     at 24h in hours
167      ztimemin1 = ztimemax1 + rjjhh * zyydd / 2            ! 21th december        in hours
168      ztimemax2 = ((6.*30.)+21.)* 24.                      ! 21th july     at 24h in hours
169      ztimemin2 = ztimemax2 - rjjhh * zyydd / 2            ! 21th january         in hours
170      !                                                    ! NB: rjjhh * zyydd / 4 = one seasonal cycle in hours
171
172      ! amplitudes
173      zemp_S    = 0.7       ! intensity of COS in the South
174      zemp_N    = 0.8       ! intensity of COS in the North
175      zemp_sais = 0.1
176      zTstar    = 28.3      ! intemsity from 28.3 a -5 deg
177
178      ! 1/2 period between 21th June and 21th December and between 21th July and 21th January
179      zcos_sais1 = COS( (ztime - ztimemax1) / (ztimemin1 - ztimemax1) * rpi ) 
180      zcos_sais2 = COS( (ztime - ztimemax2) / (ztimemax2 - ztimemin2) * rpi )
181
182      ztrp= - 40.e0        ! retroaction term on heat fluxes (W/m2/K)
183      zconv = 3.16e-5      ! convertion factor: 1 m/yr => 3.16e-5 mm/s
184      DO jj = 1, jpj
185         DO ji = 1, jpi
186            ! domain from 15 deg to 50 deg between 27 and 28  degC at 15N, -3
187            ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
188            ! 64.5 in summer, 42.5 in winter
189            t_star = zTstar * ( 1 + 1. / 50. * zcos_sais2 )                &
190               &                    * COS( rpi * (gphit(ji,jj) - 5.)               &
191               &                    / ( 53.5 * ( 1 + 11 / 53.5 * zcos_sais2 ) * 2.) )
192            ! 23.5 deg : tropics
193            qsr (ji,jj) =  230 * COS( 3.1415 * ( gphit(ji,jj) - 23.5 * zcos_sais1 ) / ( 0.9 * 180 ) )
194            qns (ji,jj) = ztrp * ( tb(ji,jj,1) - t_star ) - qsr(ji,jj)
195            IF( gphit(ji,jj) >= 14.845 .AND. 37.2 >= gphit(ji,jj) ) THEN    ! zero at 37.8 deg, max at 24.6 deg
196               emp  (ji,jj) =   zemp_S * zconv   &
197                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (24.6 - 37.2) )  &
198                  &         * ( 1 - zemp_sais / zemp_S * zcos_sais1)
199            ELSE
200               emp (ji,jj) =  - zemp_N * zconv   &
201                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (46.8 - 37.2) )  &
202                  &         * ( 1 - zemp_sais / zemp_N * zcos_sais1 )
203            ENDIF
204         END DO
205      END DO
206      emps(:,:) = emp(:,:)
207
208      ! Compute the emp flux such as its integration on the whole domain at each time is zero
209      IF( nbench /= 1 .AND. nbit_cmp /= 1 ) THEN
210         zsumemp = 0.e0   ;   zsurf = 0.e0
211         DO jj = 1, jpj
212            DO ji = 1, jpi
213               zsumemp = zsumemp + emp(ji,jj) * tmask(ji,jj,1) * tmask_i(ji,jj)
214               zsurf   = zsurf   +              tmask(ji,jj,1) * tmask_i(ji,jj)
215            END DO
216         END DO
217
218         IF( lk_mpp )   CALL mpp_sum( zsumemp  )       ! sum over the global domain
219         IF( lk_mpp )   CALL mpp_sum( zsurf    )       ! sum over the global domain
220
221         ! Default GYRE configuration
222         zsumemp = zsumemp / zsurf
223      ELSE
224         ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
225         zsumemp = 0.e0   ;    zsurf = 0.e0
226      ENDIF
227
228      !salinity terms
229      emp (:,:) = emp(:,:) - zsumemp * tmask(:,:,1)
230      emps(:,:) = emp(:,:)
231
232
233      ! ---------------------------- !
234      !       momentum fluxes        !
235      ! ---------------------------- !
236      ! same wind as in Wico
237      !test date0 : ndate0 = 010203
238      zyear0  =   ndate0 / 10000
239      zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100
240      zday0   =   ndate0 - zyear0 * 10000 - zmonth0 * 100
241      !Calculates nday_year, day since january 1st
242      zday_year0 = (zmonth0-1)*30.+zday0
243
244      !accumulates days of previous months of this year
245      ! day (in hours) since january the 1st
246      ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &  ! incrementation in hour
247         &     - (nyear - 1) * rjjhh * zyydd          !  - nber of hours the precedent years
248      ztimemax = ((5.*30.)+21.)* 24.               ! 21th june     in hours
249      ztimemin = ztimemax + rjjhh * zyydd / 2      ! 21th december in hours
250      !                                            ! NB: rjjhh * zyydd / 4 = 1 seasonal cycle in hours
251
252      ! mean intensity at 0.105 ; srqt(2) because projected with 45deg angle
253      ztau = 0.105 / SQRT( 2. )
254      ! seasonal oscillation intensity
255      ztau_sais = 0.015
256      ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
257      DO jj = 1, jpj
258         DO ji = 1, jpi
259           ! domain from 15deg to 50deg and 1/2 period along 14deg
260           ! so 5/4 of half period with seasonal cycle
261           utau(ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
262           vtau(ji,jj) =   ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
263         END DO
264      END DO
265
266      ! module of wind stress and wind speed at T-point
267      zcoef = 1. / ( zrhoa * zcdrag ) 
268!CDIR NOVERRCHK
269      DO jj = 2, jpjm1
270!CDIR NOVERRCHK
271         DO ji = fs_2, fs_jpim1   ! vect. opt.
272            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
273            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
274            zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
275            taum(ji,jj) = zmod
276            wndm(ji,jj) = SQRT( zmod * zcoef )
277         END DO
278      END DO
279      CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
280
281      ! ---------------------------------- !
282      !  control print at first time-step  !
283      ! ---------------------------------- !
284      IF( kt == nit000 .AND. lwp ) THEN
285         WRITE(numout,*)
286         WRITE(numout,*)'sbc_gyre : analytical surface fluxes for GYRE configuration'               
287         WRITE(numout,*)'~~~~~~~~ ' 
288         WRITE(numout,*)'           nyear      = ', nyear
289         WRITE(numout,*)'           nmonth     = ', nmonth
290         WRITE(numout,*)'           nday       = ', nday
291         WRITE(numout,*)'           nday_year  = ', nday_year
292         WRITE(numout,*)'           ztime      = ', ztime
293         WRITE(numout,*)'           ztimemax   = ', ztimemax
294         WRITE(numout,*)'           ztimemin   = ', ztimemin
295         WRITE(numout,*)'           ztimemax1  = ', ztimemax1
296         WRITE(numout,*)'           ztimemin1  = ', ztimemin1
297         WRITE(numout,*)'           ztimemax2  = ', ztimemax2
298         WRITE(numout,*)'           ztimemin2  = ', ztimemin2
299         WRITE(numout,*)'           zyear0     = ', zyear0
300         WRITE(numout,*)'           zmonth0    = ', zmonth0
301         WRITE(numout,*)'           zday0      = ', zday0
302         WRITE(numout,*)'           zday_year0 = ', zday_year0
303         WRITE(numout,*)'           zyydd      = ', zyydd
304         WRITE(numout,*)'           zemp_S     = ', zemp_S
305         WRITE(numout,*)'           zemp_N     = ', zemp_N
306         WRITE(numout,*)'           zemp_sais  = ', zemp_sais
307         WRITE(numout,*)'           zTstar     = ', zTstar
308         WRITE(numout,*)'           zsumemp    = ', zsumemp
309         WRITE(numout,*)'           zsurf      = ', zsurf
310         WRITE(numout,*)'           ztrp       = ', ztrp
311         WRITE(numout,*)'           zconv      = ', zconv
312         WRITE(numout,*)'           ndastp     = ', ndastp
313         WRITE(numout,*)'           adatrj     = ', adatrj
314
315      ENDIF
316      !
317   END SUBROUTINE sbc_gyre
318
319   !!======================================================================
320END MODULE sbcana
Note: See TracBrowser for help on using the repository browser.