MODULE usrdef_sbc !!====================================================================== !! *** MODULE usrdef_sbc *** !! !! === AMM7_SURGE configuration === !! !! User defined : surface forcing of a user configuration !!====================================================================== !! History : 4.0 ! 2016-03 (S. Flavoni, G. Madec) user defined interface !! 4.0 ! 2017-12 (C. O'Neill) add necessary options for surge work - either no fluxes !! (for tide-only run) or wind and pressure only !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! usrdef_sbc : user defined surface bounday conditions in LOCK_EXCHANGE case !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers USE dom_oce ! ocean space and time domain USE sbc_oce ! Surface boundary condition: ocean fields USE sbc_ice ! Surface boundary condition: ocean fields USE fldread ! read input fields USE phycst ! physical constants USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) ! USE in_out_manager ! I/O manager USE iom USE lbclnk ! ocean lateral boundary conditions (or mpp link) USE lib_mpp ! distribued memory computing library !USE wrk_nemo ! work arrays USE timing ! Timing USE prtctl ! Print control IMPLICIT NONE PRIVATE PUBLIC usrdef_sbc_oce ! routine called in sbcmod module PUBLIC usrdef_sbc_ice_tau ! routine called by sbcice_lim.F90 for ice dynamics PUBLIC usrdef_sbc_ice_flx ! routine called by sbcice_lim.F90 for ice thermo ! !!* Namelist namsbc_usr REAL(wp) :: rn_vfac ! multiplication factor for ice/ocean velocity in the calculation of wind stress (clem) REAL(wp) :: rn_charn_const LOGICAL :: ln_use_sbc ! Surface fluxes on or not !! * Substitutions # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/OCE 4.0 , NEMO Consortium (2018) !! $Id$ !! Software governed by the CeCILL license (see ./LICENSE) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE usrdef_sbc_oce( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE usrdef_sbc *** !! !! ** Purpose : provide at each time-step the surface boundary !! condition, i.e. the momentum, heat and freshwater fluxes. !! !! ** Method : all 0 fields, for AMM7_SURGE case !! CAUTION : never mask the surface stress field ! !! !! ** Action : - if tide-only case - set to ZERO all the ocean surface boundary condition, i.e. !! utau, vtau, taum, wndm, qns, qsr, emp, sfx !! - if tide+surge case - read in wind and air pressure !! !!---------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time step INTEGER :: ios ! Local integer output status for namelist read ! CHARACTER(len=100) :: cn_dir ! Root directory for location of flux files TYPE(FLD_N) :: sn_wndi, sn_wndj ! informations about the fields to be read NAMELIST/namsbc_usr/ ln_use_sbc, cn_dir , rn_vfac, & & sn_wndi, sn_wndj, rn_charn_const !!--------------------------------------------------------------------- ! IF( kt == nit000 ) THEN REWIND( numnam_cfg ) ! Namelist namsbc_usr in configuration namelist READ ( numnam_cfg, namsbc_usr, IOSTAT = ios, ERR = 902 ) 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_surge in configuration namelist' ) IF(lwm) WRITE( numond, namsbc_usr ) IF(lwp) WRITE(numout,*)' usr_sbc : AMM7_SURGE tide only case: NO surface forcing' IF(lwp) WRITE(numout,*)' ~~~~~~~~~~~ utau = vtau = taum = wndm = qns = qsr = emp = sfx = 0' utau(:,:) = 0._wp vtau(:,:) = 0._wp taum(:,:) = 0._wp wndm(:,:) = 0._wp ! emp (:,:) = 0._wp sfx (:,:) = 0._wp qns (:,:) = 0._wp qsr (:,:) = 0._wp ! ENDIF ! END SUBROUTINE usrdef_sbc_oce SUBROUTINE usrdef_sbc_ice_tau( kt ) INTEGER, INTENT(in) :: kt ! ocean time step END SUBROUTINE usrdef_sbc_ice_tau SUBROUTINE usrdef_sbc_ice_flx( kt ) INTEGER, INTENT(in) :: kt ! ocean time step END SUBROUTINE usrdef_sbc_ice_flx !!====================================================================== END MODULE usrdef_sbc