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.
usrdef_sbc.F90 in branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/OVERFLOW/MY_SRC – NEMO

source: branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/CONFIG/OVERFLOW/MY_SRC/usrdef_sbc.F90 @ 6879

Last change on this file since 6879 was 6879, checked in by flavoni, 8 years ago

commit small modifications in ly_src routines for OVERFLOW

File size: 7.0 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_sbc  ***
4   !! Ocean forcing:  user defined momentum, heat and freshwater forcings
5   !!
6   !!                ===     Here  GYRE configuration      ===
7   !!
8   !!=====================================================================
9   !! History :  4.0   ! 2016-03  (S. Flavoni, G. Madec)  user defined interface
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_sbc    : user defined surface bounday conditions in GYRE case
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 phycst          ! physical constants
19   !
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
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   usr_def_sbc    ! routine called in sbcmod module
29
30   !! * Substitutions
31#  include "vectopt_loop_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/OPA 4.0 , NEMO Consortium (2016)
34   !! $Id: $
35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE usr_def_sbc( kt )
40      !!---------------------------------------------------------------------
41      !!                    ***  ROUTINE usr_def_sbc  ***
42      !!             
43      !! ** Purpose :   provide at each time-step the surface boundary
44      !!              condition, i.e. the momentum, heat and freshwater fluxes.
45      !!
46      !! ** Method  :   analytical seasonal cycle (all 0 fields, for overflow
47      !!              case).
48      !!                CAUTION : never mask the surface stress field !
49      !!
50      !! ** Action  : - set the ocean surface boundary condition, i.e.   
51      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
52      !!
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt   ! ocean time step
55      !!
56      !SF INTEGER  ::   ji, jj                 ! dummy loop indices
57      !SF INTEGER  ::   zyear0                 ! initial year
58      !SF INTEGER  ::   zmonth0                ! initial month
59      !SF INTEGER  ::   zday0                  ! initial day
60      !SF INTEGER  ::   zday_year0             ! initial day since january 1st
61      !SF REAL(wp) ::   ztau     , ztau_sais   ! wind intensity and of the seasonal cycle
62      !SF REAL(wp) ::   ztime                  ! time in hour
63      !SF REAL(wp) ::   ztimemax , ztimemin    ! 21th June, and 21th decem. if date0 = 1st january
64      !SF REAL(wp) ::   ztimemax1, ztimemin1   ! 21th June, and 21th decem. if date0 = 1st january
65      !SF REAL(wp) ::   ztimemax2, ztimemin2   ! 21th June, and 21th decem. if date0 = 1st january
66      !SF REAL(wp) ::   ztaun                  ! intensity
67      !SF REAL(wp) ::   zemp_s, zemp_n, zemp_sais, ztstar
68      !SF REAL(wp) ::   zcos_sais1, zcos_sais2, ztrp, zconv, t_star
69      !SF REAL(wp) ::   zsumemp, zsurf
70      !SF REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
71      !SF REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
72      !SF REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
73      !SF REAL(wp) ::   zyydd                 ! number of days in one year
74!SF -------
75!SF sbc ana:
76      REAL(wp) ::   zrhoa  = 1.22_wp      ! air density kg/m3
77      REAL(wp) ::   zcdrag = 1.5e-3_wp    ! drag coefficient
78      REAL(wp) ::   zfact, ztx            ! local scalars
79      REAL(wp) ::   zcoef, zty, zmod      !   -      -
80      INTEGER  ::   nn_tau000   =   0     !  gently increase the stress over the first ntau_rst time-steps
81      REAL(wp) ::   rn_utau0    =   0.e0  !  uniform value for the i-stress
82      REAL(wp) ::   rn_vtau0    =   0.e0  !  uniform value for the j-stress
83      REAL(wp) ::   rn_qns0     =   0.e0  !  uniform value for the total heat flux
84      REAL(wp) ::   rn_qsr0     =   0.e0  !  uniform value for the solar radiation
85      REAL(wp) ::   rn_emp0     =   0.e0  !  uniform value for the freswater budget (E-P)
86      !
87      !!---------------------------------------------------------------------
88      !
89      IF( kt == nit000 ) THEN
90         !
91         IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist'
92         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
93         IF(lwp) WRITE(numout,*)'              spin up of the stress  nn_tau000 = ', nn_tau000, ' time-steps'
94         IF(lwp) WRITE(numout,*)'              constant j-stress      rn_vtau0  = ', rn_vtau0 , ' N/m2'
95         IF(lwp) WRITE(numout,*)'              non solar heat flux    rn_qns0 = ', rn_qns0  , ' W/m2'
96         IF(lwp) WRITE(numout,*)'              solar heat flux        rn_qsr0 = ', rn_qsr0  , ' W/m2'
97         IF(lwp) WRITE(numout,*)'              net heat flux          rn_emp0 = ', rn_emp0  , ' Kg/m2/s'
98         !
99         nn_tau000 = MAX( nn_tau000, 1 )     ! must be >= 1
100         !
101         utau(:,:) = rn_utau0
102         vtau(:,:) = rn_vtau0
103         taum(:,:) = SQRT ( rn_utau0 * rn_utau0 + rn_vtau0 * rn_vtau0 )
104         wndm(:,:) = SQRT ( taum(1,1) /  ( zrhoa * zcdrag ) )
105         !
106         emp (:,:) = rn_emp0
107         sfx (:,:) = 0.0_wp
108         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp      ! including heat content associated with mass flux at SST
109         qsr (:,:) = rn_qsr0
110         !         
111      ENDIF
112
113      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
114         !
115         IF( kt <= nn_tau000 ) THEN       ! Increase the stress to its nominal value
116            !                             ! during the first nn_tau000
117            !                             time-steps
118            zfact = 0.5 * (  1. - COS( rpi * REAL( kt, wp ) / REAL( nn_tau000, wp ) )  )
119            zcoef = 1. / ( zrhoa * zcdrag )
120            ztx   = zfact * rn_utau0
121            zty   = zfact * rn_vtau0
122            zmod  = SQRT( ztx * ztx + zty * zty )
123            utau(:,:) = ztx
124            vtau(:,:) = zty
125            taum(:,:) = zmod
126            zmod = SQRT( zmod * zcoef )
127            wndm(:,:) = zmod
128         ENDIF
129         !                                ! update heat and fresh water fluxes
130         !                                ! as they may have been changed by
131         !                                sbcssr module
132         emp (:,:) = rn_emp0              ! NB: qns changes with SST if emp /= 0
133         sfx (:,:) = 0._wp
134         qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp
135         qsr (:,:) = rn_qsr0
136         !
137      ENDIF
138      !
139!SF END sbc ana
140!SF -----------
141
142   END SUBROUTINE usr_def_sbc
143
144   !!======================================================================
145END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.