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/r12083_India_uncoupled/src/OCE/USR – NEMO

source: NEMO/branches/UKMO/r12083_India_uncoupled/src/OCE/USR/usrdef_sbc.F90 @ 12453

Last change on this file since 12453 was 12453, checked in by jcastill, 4 years ago

First implementation of the branch - compiling after merge

File size: 3.7 KB
RevLine 
[6583]1MODULE usrdef_sbc
2   !!======================================================================
[6923]3   !!                     ***  MODULE  usrdef_sbc  ***
[6717]4   !!
[12453]5   !!                  ===  WAD_TEST_CASES configuration  ===
[6717]6   !!
[6923]7   !! User defined :   surface forcing of a user configuration
8   !!======================================================================
[6717]9   !! History :  4.0   ! 2016-03  (S. Flavoni, G. Madec)  user defined interface
[6583]10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
[12453]13   !!   usrdef_sbc    : user defined surface bounday conditions in WAD_TEST_CASES case
[6583]14   !!----------------------------------------------------------------------
[9124]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
[6595]19   !
[9124]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)
[12453]23   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
[6583]24
25   IMPLICIT NONE
26   PRIVATE
27
[9124]28   PUBLIC   usrdef_sbc_oce       ! routine called in sbcmod module
29   PUBLIC   usrdef_sbc_ice_tau   ! routine called by icestp.F90 for ice dynamics
30   PUBLIC   usrdef_sbc_ice_flx   ! routine called by icestp.F90 for ice thermo
[6583]31
32   !! * Substitutions
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
[9598]35   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[10068]36   !! $Id$
37   !! Software governed by the CeCILL license (see ./LICENSE)
[6583]38   !!----------------------------------------------------------------------
39CONTAINS
40
[7355]41   SUBROUTINE usrdef_sbc_oce( kt )
[6583]42      !!---------------------------------------------------------------------
[7355]43      !!                    ***  ROUTINE usrdef_sbc  ***
[6583]44      !!             
[12453]45      !! ** Purpose :   provide at each time-step the surface boundary
[6583]46      !!              condition, i.e. the momentum, heat and freshwater fluxes.
47      !!
[12453]48      !! ** Method  :   all 0 fields, for WAD_TEST_CASES case
[6583]49      !!                CAUTION : never mask the surface stress field !
50      !!
[12453]51      !! ** Action  : - set to ZERO all the ocean surface boundary condition, i.e.
[6583]52      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
53      !!
54      !!----------------------------------------------------------------------
[6595]55      INTEGER, INTENT(in) ::   kt   ! ocean time step
[6583]56      !!---------------------------------------------------------------------
[12453]57      !
58      IF( kt == nit000 ) THEN 
59         !
60         IF(lwp) WRITE(numout,*)' usr_sbc : WAD_TEST_CASES case: NO surface forcing' 
61         IF(lwp) WRITE(numout,*)' ~~~~~~~~~~~   utau = vtau = taum = wndm = qns = qsr = emp = sfx = 0' 
62         !
63         utau(:,:) = 0._wp 
64         vtau(:,:) = 0._wp 
65         taum(:,:) = 0._wp 
66         wndm(:,:) = 0._wp 
67         !
68         emp (:,:) = 0._wp 
69         sfx (:,:) = 0._wp 
70         qns (:,:) = 0._wp 
71         qsr (:,:) = 0._wp 
72         !
[6583]73      ENDIF
74      !
[7355]75   END SUBROUTINE usrdef_sbc_oce
[6583]76
[9124]77
[7355]78   SUBROUTINE usrdef_sbc_ice_tau( kt )
79      INTEGER, INTENT(in) ::   kt   ! ocean time step
80   END SUBROUTINE usrdef_sbc_ice_tau
81
[9124]82
[9019]83   SUBROUTINE usrdef_sbc_ice_flx( kt, phs, phi )
[7355]84      INTEGER, INTENT(in) ::   kt   ! ocean time step
[9019]85      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phs    ! snow thickness
86      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness
[7355]87   END SUBROUTINE usrdef_sbc_ice_flx
88
[6583]89   !!======================================================================
90END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.