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 branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 17.3 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   USE lib_fortran
22
23   USE yomhook, ONLY: lhook, dr_hook
24   USE parkind1, ONLY: jprb, jpim
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   sbc_ana    ! routine called in sbcmod module
30   PUBLIC   sbc_gyre   ! routine called in sbcmod module
31
32   !                       !!* Namelist namsbc_ana *
33   INTEGER  ::   nn_tau000  ! nb of time-step during which the surface stress
34   !                        ! increase from 0 to its nominal value
35   REAL(wp) ::   rn_utau0   ! constant wind stress value in i-direction
36   REAL(wp) ::   rn_vtau0   ! constant wind stress value in j-direction
37   REAL(wp) ::   rn_qns0    ! non solar heat flux
38   REAL(wp) ::   rn_qsr0    !     solar heat flux
39   REAL(wp) ::   rn_emp0    ! net freshwater flux
40   
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43#  include "vectopt_loop_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE sbc_ana( kt )
52      !!---------------------------------------------------------------------
53      !!                    ***  ROUTINE sbc_ana ***
54      !!             
55      !! ** Purpose :   provide at each time-step the ocean surface boundary
56      !!              condition, i.e. the momentum, heat and freshwater fluxes.
57      !!
58      !! ** Method  :   Constant and uniform surface forcing specified from
59      !!              namsbc_ana namelist parameters. All the fluxes are time
60      !!              independant except the stresses which increase from zero
61      !!              during the first nn_tau000 time-step
62      !!
63      !! ** Action  : - set the ocean surface boundary condition, i.e. 
64      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
65      !!----------------------------------------------------------------------
66      INTEGER, INTENT(in) ::   kt   ! ocean time step
67      !
68      INTEGER  ::   ios                   ! local integer
69      REAL(wp) ::   zrhoa  = 1.22_wp      ! air density kg/m3
70      REAL(wp) ::   zcdrag = 1.5e-3_wp    ! drag coefficient
71      REAL(wp) ::   zfact, ztx            ! local scalars
72      REAL(wp) ::   zcoef, zty, zmod      !   -      -
73      !!
74      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0
75      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
76      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
77      REAL(KIND=jprb)               :: zhook_handle
78
79      CHARACTER(LEN=*), PARAMETER :: RoutineName='SBC_ANA'
80
81      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
82
83      !!---------------------------------------------------------------------
84      !
85      IF( kt == nit000 ) THEN
86         !
87         REWIND( numnam_ref )              ! Namelist namsbc_ana in reference namelist : Analytical surface fluxes
88         READ  ( numnam_ref, namsbc_ana, IOSTAT = ios, ERR = 901)
89901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in reference namelist', lwp )
90
91         REWIND( numnam_cfg )              ! Namelist namsbc_ana in configuration namelist : Analytical surface fluxes
92         READ  ( numnam_cfg, namsbc_ana, IOSTAT = ios, ERR = 902 )
93902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in configuration namelist', lwp )
94         IF(lwm) WRITE ( numond, namsbc_ana )
95         !
96         IF(lwp) WRITE(numout,*)' '
97         IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist'
98         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
99         IF(lwp) WRITE(numout,*)'              spin up of the stress  nn_tau000 = ', nn_tau000, ' time-steps'
100         IF(lwp) WRITE(numout,*)'              constant i-stress      rn_utau0  = ', rn_utau0 , ' N/m2'
101         IF(lwp) WRITE(numout,*)'              constant j-stress      rn_vtau0  = ', rn_vtau0 , ' N/m2'
102         IF(lwp) WRITE(numout,*)'              non solar heat flux    rn_qns0   = ', rn_qns0  , ' W/m2'
103         IF(lwp) WRITE(numout,*)'              solar heat flux        rn_qsr0   = ', rn_qsr0  , ' W/m2'
104         IF(lwp) WRITE(numout,*)'              net heat flux          rn_emp0   = ', rn_emp0  , ' Kg/m2/s'
105         !
106         nn_tau000 = MAX( nn_tau000, 1 )     ! must be >= 1
107         !
108         utau(:,:) = rn_utau0
109         vtau(:,:) = rn_vtau0
110         taum(:,:) = SQRT ( rn_utau0 * rn_utau0 + rn_vtau0 * rn_vtau0 )
111         wndm(:,:) = SQRT ( taum(1,1) /  ( zrhoa * zcdrag ) )
112         !
113         emp (:,:) = rn_emp0
114         sfx (:,:) = 0.0_wp
115         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp      ! including heat content associated with mass flux at SST
116         qsr (:,:) = rn_qsr0
117         !         
118      ENDIF
119
120      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
121         !
122         IF( kt <= nn_tau000 ) THEN       ! Increase the stress to its nominal value
123            !                             ! during the first nn_tau000 time-steps
124            zfact = 0.5 * (  1. - COS( rpi * REAL( kt, wp ) / REAL( nn_tau000, wp ) )  )
125            zcoef = 1. / ( zrhoa * zcdrag ) 
126            ztx   = zfact * rn_utau0
127            zty   = zfact * rn_vtau0
128            zmod  = SQRT( ztx * ztx + zty * zty )
129            utau(:,:) = ztx
130            vtau(:,:) = zty
131            taum(:,:) = zmod
132            zmod = SQRT( zmod * zcoef )
133            wndm(:,:) = zmod
134         ENDIF
135         !                                ! update heat and fresh water fluxes
136         !                                ! as they may have been changed by sbcssr module
137         emp (:,:) = rn_emp0              ! NB: qns changes with SST if emp /= 0
138         sfx (:,:) = 0._wp
139         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp
140         qsr (:,:) = rn_qsr0
141         !
142      ENDIF
143      !
144      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
145   END SUBROUTINE sbc_ana
146
147
148   SUBROUTINE sbc_gyre( kt )
149      !!---------------------------------------------------------------------
150      !!                    ***  ROUTINE sbc_ana ***
151      !!             
152      !! ** Purpose :   provide at each time-step the GYRE surface boundary
153      !!              condition, i.e. the momentum, heat and freshwater fluxes.
154      !!
155      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
156      !!                CAUTION : never mask the surface stress field !
157      !!
158      !! ** Action  : - set the ocean surface boundary condition, i.e.   
159      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
160      !!
161      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
162      !!----------------------------------------------------------------------
163      INTEGER, INTENT(in) ::   kt          ! ocean time step
164      !!
165      INTEGER  ::   ji, jj                 ! dummy loop indices
166      INTEGER  ::   zyear0                 ! initial year
167      INTEGER  ::   zmonth0                ! initial month
168      INTEGER  ::   zday0                  ! initial day
169      INTEGER  ::   zday_year0             ! initial day since january 1st
170      REAL(wp) ::   ztau     , ztau_sais   ! wind intensity and of the seasonal cycle
171      REAL(wp) ::   ztime                  ! time in hour
172      REAL(wp) ::   ztimemax , ztimemin    ! 21th June, and 21th decem. if date0 = 1st january
173      REAL(wp) ::   ztimemax1, ztimemin1   ! 21th June, and 21th decem. if date0 = 1st january
174      REAL(wp) ::   ztimemax2, ztimemin2   ! 21th June, and 21th decem. if date0 = 1st january
175      REAL(wp) ::   ztaun                  ! intensity
176      REAL(wp) ::   zemp_s, zemp_n, zemp_sais, ztstar
177      REAL(wp) ::   zcos_sais1, zcos_sais2, ztrp, zconv, t_star
178      REAL(wp) ::   zsumemp, zsurf
179      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
180      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
181      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
182      REAL(wp) ::   zyydd                 ! number of days in one year
183      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
184      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
185      REAL(KIND=jprb)               :: zhook_handle
186
187      CHARACTER(LEN=*), PARAMETER :: RoutineName='SBC_GYRE'
188
189      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
190
191      !!---------------------------------------------------------------------
192      zyydd = REAL(nyear_len(1),wp)
193
194      ! ---------------------------- !
195      !  heat and freshwater fluxes  !
196      ! ---------------------------- !
197      !same temperature, E-P as in HAZELEGER 2000
198
199      zyear0     =   ndate0 / 10000                             ! initial year
200      zmonth0    = ( ndate0 - zyear0 * 10000 ) / 100            ! initial month
201      zday0      =   ndate0 - zyear0 * 10000 - zmonth0 * 100    ! initial day betwen 1 and 30
202      zday_year0 = ( zmonth0 - 1 ) * 30.+zday0                  ! initial day betwen 1 and 360
203
204      ! current day (in hours) since january the 1st of the current year
205      ztime = REAL( kt ) * rdt / (rmmss * rhhmm)   &       !  total incrementation (in hours)
206         &      - (nyear  - 1) * rjjhh * zyydd             !  minus years since beginning of experiment (in hours)
207
208      ztimemax1 = ((5.*30.)+21.)* 24.                      ! 21th june     at 24h in hours
209      ztimemin1 = ztimemax1 + rjjhh * zyydd / 2            ! 21th december        in hours
210      ztimemax2 = ((6.*30.)+21.)* 24.                      ! 21th july     at 24h in hours
211      ztimemin2 = ztimemax2 - rjjhh * zyydd / 2            ! 21th january         in hours
212      !                                                    ! NB: rjjhh * zyydd / 4 = one seasonal cycle in hours
213
214      ! amplitudes
215      zemp_S    = 0.7       ! intensity of COS in the South
216      zemp_N    = 0.8       ! intensity of COS in the North
217      zemp_sais = 0.1
218      zTstar    = 28.3      ! intemsity from 28.3 a -5 deg
219
220      ! 1/2 period between 21th June and 21th December and between 21th July and 21th January
221      zcos_sais1 = COS( (ztime - ztimemax1) / (ztimemin1 - ztimemax1) * rpi ) 
222      zcos_sais2 = COS( (ztime - ztimemax2) / (ztimemax2 - ztimemin2) * rpi )
223
224      ztrp= - 40.e0        ! retroaction term on heat fluxes (W/m2/K)
225      zconv = 3.16e-5      ! convertion factor: 1 m/yr => 3.16e-5 mm/s
226      DO jj = 1, jpj
227         DO ji = 1, jpi
228            ! domain from 15 deg to 50 deg between 27 and 28  degC at 15N, -3
229            ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
230            ! 64.5 in summer, 42.5 in winter
231            t_star = zTstar * ( 1 + 1. / 50. * zcos_sais2 )                &
232               &                    * COS( rpi * (gphit(ji,jj) - 5.)               &
233               &                    / ( 53.5 * ( 1 + 11 / 53.5 * zcos_sais2 ) * 2.) )
234            ! 23.5 deg : tropics
235            qsr (ji,jj) =  230 * COS( 3.1415 * ( gphit(ji,jj) - 23.5 * zcos_sais1 ) / ( 0.9 * 180 ) )
236            qns (ji,jj) = ztrp * ( tsb(ji,jj,1,jp_tem) - t_star ) - qsr(ji,jj)
237            IF( gphit(ji,jj) >= 14.845 .AND. 37.2 >= gphit(ji,jj) ) THEN    ! zero at 37.8 deg, max at 24.6 deg
238               emp  (ji,jj) =   zemp_S * zconv   &
239                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (24.6 - 37.2) )  &
240                  &         * ( 1 - zemp_sais / zemp_S * zcos_sais1)
241            ELSE
242               emp (ji,jj) =  - zemp_N * zconv   &
243                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (46.8 - 37.2) )  &
244                  &         * ( 1 - zemp_sais / zemp_N * zcos_sais1 )
245            ENDIF
246         END DO
247      END DO
248
249      ! Compute the emp flux such as its integration on the whole domain at each time is zero
250      IF( nbench /= 1 ) THEN
251         zsumemp = GLOB_SUM( emp(:,:) ) 
252         zsurf   = GLOB_SUM( tmask(:,:,1) ) 
253         ! Default GYRE configuration
254         zsumemp = zsumemp / zsurf
255      ELSE
256         ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
257         zsumemp = 0.e0   ;    zsurf = 0.e0
258      ENDIF
259
260      ! freshwater (mass flux) and update of qns with heat content of emp
261      emp (:,:) = emp(:,:) - zsumemp * tmask(:,:,1)        ! freshwater flux (=0 in domain average)
262      sfx (:,:) = 0.0_wp                                   ! no salt flux
263      qns (:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp   ! evap and precip are at SST
264
265
266      ! ---------------------------- !
267      !       momentum fluxes        !
268      ! ---------------------------- !
269      ! same wind as in Wico
270      !test date0 : ndate0 = 010203
271      zyear0  =   ndate0 / 10000
272      zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100
273      zday0   =   ndate0 - zyear0 * 10000 - zmonth0 * 100
274      !Calculates nday_year, day since january 1st
275      zday_year0 = (zmonth0-1)*30.+zday0
276
277      !accumulates days of previous months of this year
278      ! day (in hours) since january the 1st
279      ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &  ! incrementation in hour
280         &     - (nyear - 1) * rjjhh * zyydd          !  - nber of hours the precedent years
281      ztimemax = ((5.*30.)+21.)* 24.               ! 21th june     in hours
282      ztimemin = ztimemax + rjjhh * zyydd / 2      ! 21th december in hours
283      !                                            ! NB: rjjhh * zyydd / 4 = 1 seasonal cycle in hours
284
285      ! mean intensity at 0.105 ; srqt(2) because projected with 45deg angle
286      ztau = 0.105 / SQRT( 2. )
287      ! seasonal oscillation intensity
288      ztau_sais = 0.015
289      ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
290      DO jj = 1, jpj
291         DO ji = 1, jpi
292           ! domain from 15deg to 50deg and 1/2 period along 14deg
293           ! so 5/4 of half period with seasonal cycle
294           utau(ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
295           vtau(ji,jj) =   ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
296         END DO
297      END DO
298
299      ! module of wind stress and wind speed at T-point
300      zcoef = 1. / ( zrhoa * zcdrag ) 
301!CDIR NOVERRCHK
302      DO jj = 2, jpjm1
303!CDIR NOVERRCHK
304         DO ji = fs_2, fs_jpim1   ! vect. opt.
305            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
306            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
307            zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
308            taum(ji,jj) = zmod
309            wndm(ji,jj) = SQRT( zmod * zcoef )
310         END DO
311      END DO
312      CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
313
314      ! ---------------------------------- !
315      !  control print at first time-step  !
316      ! ---------------------------------- !
317      IF( kt == nit000 .AND. lwp ) THEN
318         WRITE(numout,*)
319         WRITE(numout,*)'sbc_gyre : analytical surface fluxes for GYRE configuration'               
320         WRITE(numout,*)'~~~~~~~~ ' 
321         WRITE(numout,*)'           nyear      = ', nyear
322         WRITE(numout,*)'           nmonth     = ', nmonth
323         WRITE(numout,*)'           nday       = ', nday
324         WRITE(numout,*)'           nday_year  = ', nday_year
325         WRITE(numout,*)'           ztime      = ', ztime
326         WRITE(numout,*)'           ztimemax   = ', ztimemax
327         WRITE(numout,*)'           ztimemin   = ', ztimemin
328         WRITE(numout,*)'           ztimemax1  = ', ztimemax1
329         WRITE(numout,*)'           ztimemin1  = ', ztimemin1
330         WRITE(numout,*)'           ztimemax2  = ', ztimemax2
331         WRITE(numout,*)'           ztimemin2  = ', ztimemin2
332         WRITE(numout,*)'           zyear0     = ', zyear0
333         WRITE(numout,*)'           zmonth0    = ', zmonth0
334         WRITE(numout,*)'           zday0      = ', zday0
335         WRITE(numout,*)'           zday_year0 = ', zday_year0
336         WRITE(numout,*)'           zyydd      = ', zyydd
337         WRITE(numout,*)'           zemp_S     = ', zemp_S
338         WRITE(numout,*)'           zemp_N     = ', zemp_N
339         WRITE(numout,*)'           zemp_sais  = ', zemp_sais
340         WRITE(numout,*)'           zTstar     = ', zTstar
341         WRITE(numout,*)'           zsumemp    = ', zsumemp
342         WRITE(numout,*)'           zsurf      = ', zsurf
343         WRITE(numout,*)'           ztrp       = ', ztrp
344         WRITE(numout,*)'           zconv      = ', zconv
345         WRITE(numout,*)'           ndastp     = ', ndastp
346         WRITE(numout,*)'           adatrj     = ', adatrj
347      ENDIF
348      !
349      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
350   END SUBROUTINE sbc_gyre
351
352   !!======================================================================
353END MODULE sbcana
Note: See TracBrowser for help on using the repository browser.