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-TRUNK_r14960_HPG/tests/ADIAB_WAVE/MY_SRC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0-TRUNK_r14960_HPG/tests/ADIAB_WAVE/MY_SRC/usrdef_sbc.F90 @ 15719

Last change on this file since 15719 was 15719, checked in by dbruciaferri, 2 years ago

updating tests from git repo

File size: 3.9 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                     ***  MODULE  usrdef_sbc  ***
4   !!
5   !!                     ===  ADIAB_WAVE configuration  ===
6   !!
7   !! User defined :   surface forcing of a user configuration
8   !!======================================================================
9   !! History :  4.0   ! 2016-03  (S. Flavoni, G. Madec)  user defined interface
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   usrdef_sbc    : user defined surface bounday conditions in ADIAB_WAVE 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 sbcwave
19   USE phycst         ! physical constants
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    !
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 "do_loop_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
37   !! $Id: usrdef_sbc.F90 14433 2021-02-11 08:06:49Z smasson $
38   !! Software governed by the CeCILL license (see ./LICENSE)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE usrdef_sbc_oce( kt, Kbb )
43      !!---------------------------------------------------------------------
44      !!                    ***  ROUTINE usrdef_sbc  ***
45      !!             
46      !! ** Purpose :   provide at each time-step the ADIAB_WAVE surface boundary
47      !!              condition, i.e. the momentum, heat and freshwater fluxes.
48      !!
49      !! ** Action  : - set the ocean surface boundary condition, i.e.   
50      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
51      !!
52      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt   ! ocean time step
55      INTEGER, INTENT(in) ::   Kbb  ! ocean time index
56      !!
57      !!---------------------------------------------------------------------
58      ! ---------------------------------- !
59      !  control print at first time-step  !
60      ! ---------------------------------- !
61      IF( kt == nit000 .AND. lwp ) THEN
62         WRITE(numout,*)
63         WRITE(numout,*)'usrdef_sbc_oce : ADIAB_WAVE case: NO surface forcing'               
64         WRITE(numout,*)'utau = vtau = taum = wndm = qns = qsr = emp = sfx = 0'
65         WRITE(numout,*)'~~~~~~~~~~~ ' 
66      ENDIF
67         !
68         utau(:,:) = 0._wp
69         vtau(:,:) = 0._wp
70         taum(:,:) = 0._wp
71         wndm(:,:) = 0._wp
72         !
73         emp (:,:) = 0._wp
74         sfx (:,:) = 0._wp
75         qns (:,:) = 0._wp
76         qsr (:,:) = 0._wp
77
78      !
79      IF( ln_wave ) CALL sbc_wave ( kt, Kbb )
80   END SUBROUTINE usrdef_sbc_oce
81
82
83   SUBROUTINE usrdef_sbc_ice_tau( kt )
84      INTEGER, INTENT(in) ::   kt   ! ocean time step
85   END SUBROUTINE usrdef_sbc_ice_tau
86
87
88   SUBROUTINE usrdef_sbc_ice_flx( kt, phs, phi )
89      INTEGER, INTENT(in) ::   kt   ! ocean time step
90      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phs    ! snow thickness
91      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness
92   END SUBROUTINE usrdef_sbc_ice_flx
93
94   !!======================================================================
95END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.