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 NEMO/branches/UKMO/NEMO_4.0.1_mirror/tests/CANAL/MY_SRC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.1_mirror/tests/CANAL/MY_SRC/usrdef_sbc.F90 @ 11715

Last change on this file since 11715 was 11715, checked in by davestorkey, 4 years ago

UKMO/NEMO_4.0.1_mirror : Remove SVN keywords.

File size: 4.5 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_sbc  ***
4   !!
5   !!                      ===  CANAL configuration  ===
6   !!
7   !! User defined :   surface forcing of a user configuration
8   !!======================================================================
9   !! History :  4.0   ! 2017-11  (J.Chanut)  user defined interface
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usr_def_sbc    : user defined surface bounday conditions in OVERFLOW 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   USE usrdef_nam, ONLY : rn_u10, rn_uofac, rn_windszy 
20   !
21   USE in_out_manager  ! I/O manager
22   USE lib_mpp         ! distribued memory computing library
23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
24   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   usrdef_sbc_oce      ! routine called in sbcmod module
30   PUBLIC   usrdef_sbc_ice_tau  ! routine called by icestp.F90 for ice dynamics
31   PUBLIC   usrdef_sbc_ice_flx  ! routine called by icestp.F90 for ice thermo
32
33   !! * Substitutions
34#  include "vectopt_loop_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
37   !! $Id$
38   !! Software governed by the CeCILL license (see ./LICENSE)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE usrdef_sbc_oce( kt )
43      !!---------------------------------------------------------------------
44      !!                    ***  ROUTINE usr_def_sbc  ***
45      !!             
46      !! ** Purpose :   provide at each time-step the surface boundary
47      !!              condition, i.e. the momentum, heat and freshwater fluxes.
48      !!
49      !! ** Method  :   all 0 fields, for CANAL case
50      !!                CAUTION : never mask the surface stress field !
51      !!
52      !! ** Action  : - set to ZERO all the ocean surface boundary condition, i.e.   
53      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
54      !!
55      !!----------------------------------------------------------------------
56      INTEGER, INTENT(in) ::   kt   ! ocean time step
57     
58      INTEGER  ::   ji, jj               ! dummy loop indices
59      REAL(wp) :: zrhoair = 1.22     ! approximate air density [Kg/m3]
60      REAL(wp) :: zcd = 1.13e-3      ! approximate drag coefficient
61      REAL(wp) :: zrhocd             ! Rho * Cd
62      REAL(wp), DIMENSION(jpi,jpj) :: zwndrel   ! relative wind
63      !!---------------------------------------------------------------------
64      !
65      zrhocd = zrhoair * zcd
66     
67      IF( kt == nit000 ) THEN
68         !
69         IF(lwp) WRITE(numout,*)' usr_sbc : EW_CANAL case: surface forcing'
70         IF(lwp) WRITE(numout,*)' ~~~~~~~~~~~   vtau = taum = wndm = qns = qsr = emp = sfx = 0'
71         !
72         utau(:,:) = 0._wp
73         IF( rn_u10 /= 0. .AND. rn_windszy > 0. ) THEN
74            WHERE( ABS(gphit) <= rn_windszy/2. ) utau(:,:) = zrhocd * rn_u10 * rn_u10
75         ENDIF
76         vtau(:,:) = 0._wp
77         taum(:,:) = 0._wp
78         wndm(:,:) = 0._wp
79         !
80         emp (:,:) = 0._wp
81         sfx (:,:) = 0._wp
82         qns (:,:) = 0._wp
83         qsr (:,:) = 0._wp
84         !         
85      ENDIF
86
87      IF( rn_uofac /= 0. ) THEN
88         
89         WHERE( ABS(gphit) <= rn_windszy/2. )
90            zwndrel(:,:) = rn_u10 - rn_uofac * un(:,:,1)
91         ELSEWHERE
92            zwndrel(:,:) =        - rn_uofac * un(:,:,1)
93         END WHERE
94         utau(:,:) = zrhocd * zwndrel(:,:) * zwndrel(:,:)
95
96         zwndrel(:,:) = - rn_uofac * vn(:,:,1)
97         vtau(:,:) = zrhocd * zwndrel(:,:) * zwndrel(:,:)
98
99      ENDIF
100      !
101   END SUBROUTINE usrdef_sbc_oce
102
103   SUBROUTINE usrdef_sbc_ice_tau( kt )
104      INTEGER, INTENT(in) ::   kt   ! ocean time step
105   END SUBROUTINE usrdef_sbc_ice_tau
106
107   SUBROUTINE usrdef_sbc_ice_flx( kt )
108      INTEGER, INTENT(in) ::   kt   ! ocean time step
109   END SUBROUTINE usrdef_sbc_ice_flx
110
111   !!======================================================================
112END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.