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/2020/dev_r13327_KERNEL-06_2_techene_e3/tests/AM98/MY_SRC – NEMO

source: NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/tests/AM98/MY_SRC/usrdef_sbc.F90 @ 13503

Last change on this file since 13503 was 13503, checked in by techene, 4 years ago

files copied from dev_r12527_Gurvan_ShallowWater see #2385

File size: 5.1 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                     ***  MODULE  usrdef_sbc  ***
4   !!
5   !!                     ===  GYRE 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 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   USE usrdef_nam
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   !!----------------------------------------------------------------------
34   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
35   !! $Id: usrdef_sbc.F90 10425 2018-12-19 21:54:16Z smasson $
36   !! Software governed by the CeCILL license (see ./LICENSE)
37   !!----------------------------------------------------------------------
38CONTAINS
39
40   SUBROUTINE usrdef_sbc_oce( kt, Kbb )
41      !!---------------------------------------------------------------------
42      !!                    ***  ROUTINE usrdef_sbc  ***
43      !!             
44      !! ** Purpose :   provide at each time-step the GYRE surface boundary
45      !!              condition, i.e. the momentum, heat and freshwater fluxes.
46      !!
47      !! ** Method  :   analytical seasonal cycle for GYRE configuration.
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      !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! ocean time step
56      INTEGER, INTENT(in) ::   Kbb  ! ocean time index
57      !!
58      INTEGER  ::   ji, jj                ! dummy loop indices
59      REAL(wp) ::   ztauu, ztauv          ! wind intensity projeted
60      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
61      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
62      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
63      !!---------------------------------------------------------------------
64
65      ! ---------------------------- !
66      !  heat and freshwater fluxes  !   (no fluxes)
67      ! ---------------------------- !
68     
69      emp (:,:) = 0._wp
70      sfx (:,:) = 0._wp
71      qns (:,:) = 0._wp
72
73      ! ---------------------------- !
74      !       momentum fluxes        !
75      ! ---------------------------- !
76      ! rotated case (45deg)
77      ! ztauu = 0.2_wp / SQRT( 2._wp )    ! N.m-2
78      ! ztauv = 0.2_wp / SQRT( 2._wp)     ! N.m-2
79      ! non rotated
80      !ztauu = 0.2_wp                    ! N.m-2
81      !ztauv = 0._wp                     ! N.m-2
82      ! general case
83      ztauu =   REAL( rn_tau, wp ) * COS( rn_theta * rad )   ! N.m-2
84      ztauv = - REAL( rn_tau, wp ) * SIN( rn_theta * rad )   ! N.m-2
85     
86      DO jj = 1, jpj
87         DO ji = 1, jpi
88           ! length of the domain : 2000km x 2000km
89           utau(ji,jj) = - ztauu * COS( rpi * gphiu(ji,jj) / 2000000._wp)
90           vtau(ji,jj) = - ztauv * COS( rpi * gphiv(ji,jj) / 2000000._wp)
91         END DO
92      END DO
93     
94      ! module of wind stress and wind speed at T-point
95      zcoef = 1. / ( zrhoa * zcdrag ) 
96      DO jj = 2, jpjm1
97         DO ji = 2, jpim1
98            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
99            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
100            zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
101            taum(ji,jj) = zmod
102            wndm(ji,jj) = SQRT( zmod * zcoef )
103         END DO
104      END DO
105     
106      CALL lbc_lnk_multi( 'usrdef_sbc', taum(:,:), 'T', 1. , wndm(:,:), 'T', 1. )
107      !
108   END SUBROUTINE usrdef_sbc_oce
109
110
111   SUBROUTINE usrdef_sbc_ice_tau( kt )
112      INTEGER, INTENT(in) ::   kt   ! ocean time step
113   END SUBROUTINE usrdef_sbc_ice_tau
114
115
116   SUBROUTINE usrdef_sbc_ice_flx( kt, phs, phi )
117      INTEGER, INTENT(in) ::   kt   ! ocean time step
118      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phs    ! snow thickness
119      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness
120   END SUBROUTINE usrdef_sbc_ice_flx
121
122   !!======================================================================
123END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.