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/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90 @ 7158

Last change on this file since 7158 was 7158, checked in by clem, 7 years ago

debug branch

  • Property svn:keywords set to Id
File size: 20.9 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   !!            3.7   ! 2016-10  (C. Rousset)  Add analytic for LIM3 (ana_ice)
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   sbc_ana  : set an analytical ocean forcing
13   !!   sbc_gyre : set the GYRE configuration analytical forcing
14   !!----------------------------------------------------------------------
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE sbc_oce         ! Surface boundary condition: ocean fields
18   USE sbc_ice         ! Surface boundary condition: ice   fields
19   USE phycst          ! physical constants
20   USE in_out_manager  ! I/O manager
21   USE lib_mpp         ! distribued memory computing library
22   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
23   USE lib_fortran
24   USE wrk_nemo
25#if defined key_lim3
26   USE ice, ONLY       : pfrld, a_i_b
27   USE limthd_dh       ! for CALL lim_thd_snwblow
28#endif
29   
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   sbc_ana         ! routine called in sbcmod module
34   PUBLIC   sbc_gyre        ! routine called in sbcmod module
35#if defined key_lim3
36   PUBLIC   ana_ice_tau     ! routine called in sbc_ice_lim module
37   PUBLIC   ana_ice_flx     ! routine called in sbc_ice_lim module
38#endif
39
40   !                       !!* Namelist namsbc_ana *
41   ! --- oce variables --- !
42   INTEGER  ::   nn_tau000 ! nb of time-step during which the surface stress
43   !                       ! increase from 0 to its nominal value
44   REAL(wp) ::   rn_utau0  ! constant wind stress value in i-direction
45   REAL(wp) ::   rn_vtau0  ! constant wind stress value in j-direction
46   REAL(wp) ::   rn_qns0   ! non solar heat flux
47   REAL(wp) ::   rn_qsr0   !     solar heat flux
48   REAL(wp) ::   rn_emp0   ! net freshwater flux
49   ! --- ice variables --- !
50   REAL(wp) ::   rn_iutau0 ! constant wind stress value in i-direction over ice
51   REAL(wp) ::   rn_ivtau0 ! constant wind stress value in j-direction over ice
52   REAL(wp) ::   rn_iqns0  ! non solar heat flux over ice
53   REAL(wp) ::   rn_iqsr0  !     solar heat flux over ice
54   REAL(wp) ::   rn_sprec0 ! snow precip
55   REAL(wp) ::   rn_ievap0 ! sublimation
56   
57   !! * Substitutions
58#  include "domzgr_substitute.h90"
59#  include "vectopt_loop_substitute.h90"
60   !!----------------------------------------------------------------------
61   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
62   !! $Id$
63   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
64   !!----------------------------------------------------------------------
65CONTAINS
66
67   SUBROUTINE sbc_ana( kt )
68      !!---------------------------------------------------------------------
69      !!                    ***  ROUTINE sbc_ana ***
70      !!             
71      !! ** Purpose :   provide at each time-step the ocean surface boundary
72      !!              condition, i.e. the momentum, heat and freshwater fluxes.
73      !!
74      !! ** Method  :   Constant and uniform surface forcing specified from
75      !!              namsbc_ana namelist parameters. All the fluxes are time
76      !!              independant except the stresses which increase from zero
77      !!              during the first nn_tau000 time-step
78      !!
79      !! ** Action  : - set the ocean surface boundary condition, i.e. 
80      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
81      !!----------------------------------------------------------------------
82      INTEGER, INTENT(in) ::   kt   ! ocean time step
83      !
84      INTEGER  ::   ios                   ! local integer
85      REAL(wp) ::   zrhoa  = 1.22_wp      ! air density kg/m3
86      REAL(wp) ::   zcdrag = 1.5e-3_wp    ! drag coefficient
87      REAL(wp) ::   zfact, ztx            ! local scalars
88      REAL(wp) ::   zcoef, zty, zmod      !   -      -
89      !!
90      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0,  &
91         &                 rn_iutau0, rn_ivtau0, rn_iqsr0, rn_iqns0, rn_sprec0, rn_ievap0
92      !!---------------------------------------------------------------------
93      !
94      IF( kt == nit000 ) THEN
95         !
96         REWIND( numnam_ref )              ! Namelist namsbc_ana in reference namelist : Analytical surface fluxes
97         READ  ( numnam_ref, namsbc_ana, IOSTAT = ios, ERR = 901)
98901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in reference namelist', lwp )
99
100         REWIND( numnam_cfg )              ! Namelist namsbc_ana in configuration namelist : Analytical surface fluxes
101         READ  ( numnam_cfg, namsbc_ana, IOSTAT = ios, ERR = 902 )
102902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in configuration namelist', lwp )
103         IF(lwm) WRITE ( numond, namsbc_ana )
104         !
105         IF(lwp) WRITE(numout,*)' '
106         IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist'
107         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
108         IF(lwp) WRITE(numout,*)'              spin up of the stress         nn_tau000 = ', nn_tau000 , ' time-steps'
109         IF(lwp) WRITE(numout,*)'              constant i-stress             rn_utau0  = ', rn_utau0  , ' N/m2'
110         IF(lwp) WRITE(numout,*)'              constant j-stress             rn_vtau0  = ', rn_vtau0  , ' N/m2'
111         IF(lwp) WRITE(numout,*)'              non solar heat flux           rn_qns0   = ', rn_qns0   , ' W/m2'
112         IF(lwp) WRITE(numout,*)'              solar heat flux               rn_qsr0   = ', rn_qsr0   , ' W/m2'
113         IF(lwp) WRITE(numout,*)'              net freshwater flux           rn_emp0   = ', rn_emp0   , ' Kg/m2/s'
114         IF(lwp) WRITE(numout,*)'              constant ice-atm stress       rn_iutau0 = ', rn_iutau0 , ' N/m2'
115         IF(lwp) WRITE(numout,*)'              constant ice-atm stress       rn_ivtau0 = ', rn_ivtau0 , ' N/m2'
116         IF(lwp) WRITE(numout,*)'              solar heat flux over ice      rn_iqsr0  = ', rn_iqsr0  , ' W/m2'
117         IF(lwp) WRITE(numout,*)'              non solar heat flux over ice  rn_iqns0  = ', rn_iqns0  , ' W/m2'
118         IF(lwp) WRITE(numout,*)'              snow precip                   rn_sprec0 = ', rn_sprec0 , ' Kg/m2/s'
119         IF(lwp) WRITE(numout,*)'              sublimation                   rn_ievap0 = ', rn_ievap0 , ' Kg/m2/s'
120         !
121         nn_tau000 = MAX( nn_tau000, 1 )     ! must be >= 1
122         !
123         utau(:,:) = rn_utau0
124         vtau(:,:) = rn_vtau0
125         taum(:,:) = SQRT ( rn_utau0 * rn_utau0 + rn_vtau0 * rn_vtau0 )
126         wndm(:,:) = SQRT ( taum(1,1) /  ( zrhoa * zcdrag ) )
127         !
128         emp (:,:) = rn_emp0
129         sfx (:,:) = 0.0_wp
130         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp      ! including heat content associated with mass flux at SST
131         qsr (:,:) = rn_qsr0
132         !         
133      ENDIF
134
135      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
136         !
137         IF( kt <= nn_tau000 ) THEN       ! Increase the stress to its nominal value
138            !                             ! during the first nn_tau000 time-steps
139            zfact = 0.5 * (  1. - COS( rpi * REAL( kt, wp ) / REAL( nn_tau000, wp ) )  )
140            zcoef = 1. / ( zrhoa * zcdrag ) 
141            ztx   = zfact * rn_utau0
142            zty   = zfact * rn_vtau0
143            zmod  = SQRT( ztx * ztx + zty * zty )
144            utau(:,:) = ztx
145            vtau(:,:) = zty
146            taum(:,:) = zmod
147            zmod = SQRT( zmod * zcoef )
148            wndm(:,:) = zmod
149         ENDIF
150         !                                ! update heat and fresh water fluxes
151         !                                ! as they may have been changed by sbcssr module
152         emp (:,:) = rn_emp0              ! NB: qns changes with SST if emp /= 0
153         sfx (:,:) = 0._wp
154         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp
155         qsr (:,:) = rn_qsr0
156         !
157      ENDIF
158      !
159   END SUBROUTINE sbc_ana
160
161#if defined key_lim3
162   SUBROUTINE ana_ice_tau
163      !!---------------------------------------------------------------------
164      !!                     ***  ROUTINE ana_ice_tau  ***
165      !!
166      !! ** Purpose :   provide the surface boundary (momentum) condition over sea-ice
167      !!---------------------------------------------------------------------
168      utau_ice(:,:) = rn_iutau0
169      vtau_ice(:,:) = rn_ivtau0
170     
171   END SUBROUTINE ana_ice_tau
172   
173   SUBROUTINE ana_ice_flx
174      !!---------------------------------------------------------------------
175      !!                     ***  ROUTINE ana_ice_flx  ***
176      !!
177      !! ** Purpose :   provide the surface boundary (flux) condition over sea-ice
178      !!---------------------------------------------------------------------
179      REAL(wp), DIMENSION(:,:), POINTER ::   zsnw       ! snw distribution after wind blowing
180      !!---------------------------------------------------------------------
181      CALL wrk_alloc( jpi,jpj, zsnw ) 
182
183      ! ocean variables (renaming)
184      emp_oce (:,:)   = rn_emp0
185      qsr_oce (:,:)   = rn_qsr0
186      qns_oce (:,:)   = rn_qns0
187     
188      ! ice variables
189      alb_ice (:,:,:) = 0.7_wp ! useless
190      qsr_ice (:,:,:) = rn_iqsr0
191      qns_ice (:,:,:) = rn_iqns0
192      sprecip (:,:)   = rn_sprec0
193      evap_ice(:,:,:) = rn_ievap0
194
195      ! ice variables deduced from above
196      zsnw(:,:) = 1._wp
197      !!CALL lim_thd_snwblow( pfrld, zsnw )  ! snow distribution over ice after wind blowing
198      emp_ice  (:,:)   = SUM( a_i_b(:,:,:) * evap_ice(:,:,:), dim=3 ) - sprecip(:,:) * zsnw(:,:)
199      emp_oce  (:,:)   = emp_oce(:,:) - sprecip(:,:) * (1._wp - zsnw(:,:) )
200      qevap_ice(:,:,:) =   0._wp
201      qprec_ice(:,:)   =   rhosn * ( sst_m(:,:) * cpic - lfus ) * tmask(:,:,1) ! in J/m3
202      qemp_oce (:,:)   = - emp_oce(:,:) * sst_m(:,:) * rcp
203      qemp_ice (:,:)   =   sprecip(:,:) * zsnw * ( sst_m(:,:) * cpic - lfus ) * tmask(:,:,1) ! solid precip (only)
204
205      ! total fluxes
206      emp_tot (:,:) = emp_ice  + emp_oce 
207      qns_tot (:,:) = pfrld(:,:) * qns_oce(:,:) + SUM( a_i_b(:,:,:) * qns_ice(:,:,:), dim=3 ) + qemp_ice(:,:) + qemp_oce(:,:)
208      qsr_tot (:,:) = pfrld(:,:) * qsr_oce(:,:) + SUM( a_i_b(:,:,:) * qsr_ice(:,:,:), dim=3 )
209
210      !--------------------------------------------------------------------
211      ! FRACTIONs of net shortwave radiation which is not absorbed in the
212      ! thin surface layer and penetrates inside the ice cover
213      ! ( Maykut and Untersteiner, 1971 ; Ebert and Curry, 1993 )
214      fr1_i0(:,:) = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )
215      fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )
216
217      CALL wrk_dealloc( jpi,jpj, zsnw ) 
218     
219   END SUBROUTINE ana_ice_flx
220#endif
221
222   
223   SUBROUTINE sbc_gyre( kt )
224      !!---------------------------------------------------------------------
225      !!                    ***  ROUTINE sbc_ana ***
226      !!             
227      !! ** Purpose :   provide at each time-step the GYRE surface boundary
228      !!              condition, i.e. the momentum, heat and freshwater fluxes.
229      !!
230      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
231      !!                CAUTION : never mask the surface stress field !
232      !!
233      !! ** Action  : - set the ocean surface boundary condition, i.e.   
234      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
235      !!
236      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
237      !!----------------------------------------------------------------------
238      INTEGER, INTENT(in) ::   kt          ! ocean time step
239      !!
240      INTEGER  ::   ji, jj                 ! dummy loop indices
241      INTEGER  ::   zyear0                 ! initial year
242      INTEGER  ::   zmonth0                ! initial month
243      INTEGER  ::   zday0                  ! initial day
244      INTEGER  ::   zday_year0             ! initial day since january 1st
245      REAL(wp) ::   ztau     , ztau_sais   ! wind intensity and of the seasonal cycle
246      REAL(wp) ::   ztime                  ! time in hour
247      REAL(wp) ::   ztimemax , ztimemin    ! 21th June, and 21th decem. if date0 = 1st january
248      REAL(wp) ::   ztimemax1, ztimemin1   ! 21th June, and 21th decem. if date0 = 1st january
249      REAL(wp) ::   ztimemax2, ztimemin2   ! 21th June, and 21th decem. if date0 = 1st january
250      REAL(wp) ::   ztaun                  ! intensity
251      REAL(wp) ::   zemp_s, zemp_n, zemp_sais, ztstar
252      REAL(wp) ::   zcos_sais1, zcos_sais2, ztrp, zconv, t_star
253      REAL(wp) ::   zsumemp, zsurf
254      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
255      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
256      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
257      REAL(wp) ::   zyydd                 ! number of days in one year
258      !!---------------------------------------------------------------------
259      zyydd = REAL(nyear_len(1),wp)
260
261      ! ---------------------------- !
262      !  heat and freshwater fluxes  !
263      ! ---------------------------- !
264      !same temperature, E-P as in HAZELEGER 2000
265
266      zyear0     =   ndate0 / 10000                             ! initial year
267      zmonth0    = ( ndate0 - zyear0 * 10000 ) / 100            ! initial month
268      zday0      =   ndate0 - zyear0 * 10000 - zmonth0 * 100    ! initial day betwen 1 and 30
269      zday_year0 = ( zmonth0 - 1 ) * 30.+zday0                  ! initial day betwen 1 and 360
270
271      ! current day (in hours) since january the 1st of the current year
272      ztime = REAL( kt ) * rdt / (rmmss * rhhmm)   &       !  total incrementation (in hours)
273         &      - (nyear  - 1) * rjjhh * zyydd             !  minus years since beginning of experiment (in hours)
274
275      ztimemax1 = ((5.*30.)+21.)* 24.                      ! 21th june     at 24h in hours
276      ztimemin1 = ztimemax1 + rjjhh * zyydd / 2            ! 21th december        in hours
277      ztimemax2 = ((6.*30.)+21.)* 24.                      ! 21th july     at 24h in hours
278      ztimemin2 = ztimemax2 - rjjhh * zyydd / 2            ! 21th january         in hours
279      !                                                    ! NB: rjjhh * zyydd / 4 = one seasonal cycle in hours
280
281      ! amplitudes
282      zemp_S    = 0.7       ! intensity of COS in the South
283      zemp_N    = 0.8       ! intensity of COS in the North
284      zemp_sais = 0.1
285      zTstar    = 28.3      ! intemsity from 28.3 a -5 deg
286
287      ! 1/2 period between 21th June and 21th December and between 21th July and 21th January
288      zcos_sais1 = COS( (ztime - ztimemax1) / (ztimemin1 - ztimemax1) * rpi ) 
289      zcos_sais2 = COS( (ztime - ztimemax2) / (ztimemax2 - ztimemin2) * rpi )
290
291      ztrp= - 40.e0        ! retroaction term on heat fluxes (W/m2/K)
292      zconv = 3.16e-5      ! convertion factor: 1 m/yr => 3.16e-5 mm/s
293      DO jj = 1, jpj
294         DO ji = 1, jpi
295            ! domain from 15 deg to 50 deg between 27 and 28  degC at 15N, -3
296            ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
297            ! 64.5 in summer, 42.5 in winter
298            t_star = zTstar * ( 1 + 1. / 50. * zcos_sais2 )                &
299               &                    * COS( rpi * (gphit(ji,jj) - 5.)               &
300               &                    / ( 53.5 * ( 1 + 11 / 53.5 * zcos_sais2 ) * 2.) )
301            ! 23.5 deg : tropics
302            qsr (ji,jj) =  230 * COS( 3.1415 * ( gphit(ji,jj) - 23.5 * zcos_sais1 ) / ( 0.9 * 180 ) )
303            qns (ji,jj) = ztrp * ( tsb(ji,jj,1,jp_tem) - t_star ) - qsr(ji,jj)
304            IF( gphit(ji,jj) >= 14.845 .AND. 37.2 >= gphit(ji,jj) ) THEN    ! zero at 37.8 deg, max at 24.6 deg
305               emp  (ji,jj) =   zemp_S * zconv   &
306                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (24.6 - 37.2) )  &
307                  &         * ( 1 - zemp_sais / zemp_S * zcos_sais1)
308            ELSE
309               emp (ji,jj) =  - zemp_N * zconv   &
310                  &         * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (46.8 - 37.2) )  &
311                  &         * ( 1 - zemp_sais / zemp_N * zcos_sais1 )
312            ENDIF
313         END DO
314      END DO
315
316      ! Compute the emp flux such as its integration on the whole domain at each time is zero
317      IF( nbench /= 1 ) THEN
318         zsumemp = GLOB_SUM( emp(:,:) ) 
319         zsurf   = GLOB_SUM( tmask(:,:,1) ) 
320         ! Default GYRE configuration
321         zsumemp = zsumemp / zsurf
322      ELSE
323         ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
324         zsumemp = 0.e0   ;    zsurf = 0.e0
325      ENDIF
326
327      ! freshwater (mass flux) and update of qns with heat content of emp
328      emp (:,:) = emp(:,:) - zsumemp * tmask(:,:,1)        ! freshwater flux (=0 in domain average)
329      sfx (:,:) = 0.0_wp                                   ! no salt flux
330      qns (:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp   ! evap and precip are at SST
331
332
333      ! ---------------------------- !
334      !       momentum fluxes        !
335      ! ---------------------------- !
336      ! same wind as in Wico
337      !test date0 : ndate0 = 010203
338      zyear0  =   ndate0 / 10000
339      zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100
340      zday0   =   ndate0 - zyear0 * 10000 - zmonth0 * 100
341      !Calculates nday_year, day since january 1st
342      zday_year0 = (zmonth0-1)*30.+zday0
343
344      !accumulates days of previous months of this year
345      ! day (in hours) since january the 1st
346      ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &  ! incrementation in hour
347         &     - (nyear - 1) * rjjhh * zyydd          !  - nber of hours the precedent years
348      ztimemax = ((5.*30.)+21.)* 24.               ! 21th june     in hours
349      ztimemin = ztimemax + rjjhh * zyydd / 2      ! 21th december in hours
350      !                                            ! NB: rjjhh * zyydd / 4 = 1 seasonal cycle in hours
351
352      ! mean intensity at 0.105 ; srqt(2) because projected with 45deg angle
353      ztau = 0.105 / SQRT( 2. )
354      ! seasonal oscillation intensity
355      ztau_sais = 0.015
356      ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
357      DO jj = 1, jpj
358         DO ji = 1, jpi
359           ! domain from 15deg to 50deg and 1/2 period along 14deg
360           ! so 5/4 of half period with seasonal cycle
361           utau(ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
362           vtau(ji,jj) =   ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
363         END DO
364      END DO
365
366      ! module of wind stress and wind speed at T-point
367      zcoef = 1. / ( zrhoa * zcdrag ) 
368!CDIR NOVERRCHK
369      DO jj = 2, jpjm1
370!CDIR NOVERRCHK
371         DO ji = fs_2, fs_jpim1   ! vect. opt.
372            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
373            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
374            zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
375            taum(ji,jj) = zmod
376            wndm(ji,jj) = SQRT( zmod * zcoef )
377         END DO
378      END DO
379      CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
380
381      ! ---------------------------------- !
382      !  control print at first time-step  !
383      ! ---------------------------------- !
384      IF( kt == nit000 .AND. lwp ) THEN
385         WRITE(numout,*)
386         WRITE(numout,*)'sbc_gyre : analytical surface fluxes for GYRE configuration'               
387         WRITE(numout,*)'~~~~~~~~ ' 
388         WRITE(numout,*)'           nyear      = ', nyear
389         WRITE(numout,*)'           nmonth     = ', nmonth
390         WRITE(numout,*)'           nday       = ', nday
391         WRITE(numout,*)'           nday_year  = ', nday_year
392         WRITE(numout,*)'           ztime      = ', ztime
393         WRITE(numout,*)'           ztimemax   = ', ztimemax
394         WRITE(numout,*)'           ztimemin   = ', ztimemin
395         WRITE(numout,*)'           ztimemax1  = ', ztimemax1
396         WRITE(numout,*)'           ztimemin1  = ', ztimemin1
397         WRITE(numout,*)'           ztimemax2  = ', ztimemax2
398         WRITE(numout,*)'           ztimemin2  = ', ztimemin2
399         WRITE(numout,*)'           zyear0     = ', zyear0
400         WRITE(numout,*)'           zmonth0    = ', zmonth0
401         WRITE(numout,*)'           zday0      = ', zday0
402         WRITE(numout,*)'           zday_year0 = ', zday_year0
403         WRITE(numout,*)'           zyydd      = ', zyydd
404         WRITE(numout,*)'           zemp_S     = ', zemp_S
405         WRITE(numout,*)'           zemp_N     = ', zemp_N
406         WRITE(numout,*)'           zemp_sais  = ', zemp_sais
407         WRITE(numout,*)'           zTstar     = ', zTstar
408         WRITE(numout,*)'           zsumemp    = ', zsumemp
409         WRITE(numout,*)'           zsurf      = ', zsurf
410         WRITE(numout,*)'           ztrp       = ', ztrp
411         WRITE(numout,*)'           zconv      = ', zconv
412         WRITE(numout,*)'           ndastp     = ', ndastp
413         WRITE(numout,*)'           adatrj     = ', adatrj
414      ENDIF
415      !
416   END SUBROUTINE sbc_gyre
417
418   !!======================================================================
419END MODULE sbcana
Note: See TracBrowser for help on using the repository browser.