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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90 @ 4416

Last change on this file since 4416 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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