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/trunk/tests/DONUT/MY_SRC – NEMO

source: NEMO/trunk/tests/DONUT/MY_SRC/usrdef_sbc.F90 @ 14273

Last change on this file since 14273 was 14273, checked in by smasson, 3 years ago

trunk: fix DONUT and BENCH tests + minor fix in usrdef_sbc.F90 if icethd

File size: 6.6 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_sbc  ***
4   !!
5   !!                      ===  DONUT 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   !!   usr_def_sbc    : user defined surface bounday conditions in DONUT 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 sbc_ice         ! Surface boundary condition: ice fields
19   USE in_out_manager  ! I/O manager
20   USE phycst          ! physical constants
21#if defined key_si3
22   USE ice, ONLY       : at_i_b, a_i_b
23#endif
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   usrdef_sbc_oce      ! routine called by sbcmod.F90 for sbc ocean
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
31
32   !!----------------------------------------------------------------------
33   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
34   !! $Id: usrdef_sbc.F90 10074 2018-08-28 16:15:49Z nicolasmartin $
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE usrdef_sbc_oce( kt, Kbb )
40      !!---------------------------------------------------------------------
41      !!                    ***  ROUTINE usr_def_sbc  ***
42      !!             
43      !! ** Purpose :   provide at each time-step the surface boundary
44      !!              condition, i.e. the momentum, heat and freshwater fluxes.
45      !!
46      !! ** Method  :   all 0 fields, for DONUT case
47      !!                CAUTION : never mask the surface stress field !
48      !!
49      !! ** Action  : - set to ZERO all the ocean surface boundary condition, i.e.   
50      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
51      !!
52      !!----------------------------------------------------------------------
53      INTEGER, INTENT(in) ::   kt   ! ocean time step
54      INTEGER, INTENT(in) ::   Kbb  ! ocean time index
55      !!---------------------------------------------------------------------
56      !
57      IF( kt == nit000 ) THEN
58         !
59         IF(lwp)   WRITE(numout,*)' usrdef_sbc_oce : DONUT case: NO surface forcing'
60         ! --- oce variables --- !
61         utau(:,:) = 0._wp 
62         vtau(:,:) = 0._wp
63         taum(:,:) = 0._wp
64         wndm(:,:) = 0._wp
65         !
66         emp (:,:) = 0._wp
67         sfx (:,:) = 0._wp
68         qns (:,:) = 0._wp
69         qsr (:,:) = 0._wp
70         !
71         utau_b(:,:) = 0._wp 
72         vtau_b(:,:) = 0._wp
73         emp_b (:,:) = 0._wp
74         sfx_b (:,:) = 0._wp
75         qns_b (:,:) = 0._wp
76         !
77      ENDIF
78      !
79   END SUBROUTINE usrdef_sbc_oce
80
81
82   SUBROUTINE usrdef_sbc_ice_tau( kt )
83      !!---------------------------------------------------------------------
84      !!                     ***  ROUTINE usrdef_sbc_ice_tau  ***
85      !!
86      !! ** Purpose :   provide the surface boundary (momentum) condition over sea-ice
87      !!---------------------------------------------------------------------
88      INTEGER, INTENT(in) ::   kt   ! ocean time step
89      !!---------------------------------------------------------------------
90#if defined key_si3
91      IF( kt==nit000 .AND. lwp)   WRITE(numout,*)' usrdef_sbc_ice : DONUT case: NO stress forcing'
92      !
93      utau_ice(:,:) = 0._wp
94      vtau_ice(:,:) = 0._wp
95#endif
96      !
97   END SUBROUTINE usrdef_sbc_ice_tau
98
99
100   SUBROUTINE usrdef_sbc_ice_flx( kt, phs, phi )
101      !!---------------------------------------------------------------------
102      !!                     ***  ROUTINE usrdef_sbc_ice_flx  ***
103      !!
104      !! ** Purpose :   provide the surface boundary (flux) condition over sea-ice
105      !!---------------------------------------------------------------------
106      INTEGER, INTENT(in) ::   kt   ! ocean time step
107      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   phs    ! snow thickness
108      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   phi    ! ice thickness
109      !!
110      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw   ! snw distribution after wind blowing
111      !!---------------------------------------------------------------------
112#if defined key_si3
113      !
114      IF( kt==nit000 .AND. lwp)   WRITE(numout,*)' usrdef_sbc_ice : DONUT case: NO flux forcing'
115      !
116      ! ocean variables (renaming)
117      emp_oce (:,:)   = 0._wp   ! uniform value for freshwater budget (E-P)
118      qsr_oce (:,:)   = 0._wp   ! uniform value for     solar radiation
119      qns_oce (:,:)   = 0._wp   ! uniform value for non-solar heat flux
120
121      ! ice variables
122      alb_ice (:,:,:) = 0.7_wp  ! useless
123      qsr_ice (:,:,:) = 0._wp   ! uniform value for     solar radiation
124      qns_ice (:,:,:) = 0._wp   ! uniform value for non-solar heat flux
125      dqns_ice(:,:,:) = 0._wp   ! uniform value for non solar heat flux sensitivity for ice
126      sprecip (:,:)   = 0._wp   ! uniform value for snow precip
127      evap_ice(:,:,:) = 0._wp   ! uniform value for sublimation
128
129      ! ice fields deduced from above
130      zsnw(:,:) = 1._wp
131      !!CALL lim_thd_snwblow( at_i_b, zsnw )  ! snow distribution over ice after wind blowing
132      emp_ice  (:,:)   = SUM( a_i_b(:,:,:) * evap_ice(:,:,:), dim=3 ) - sprecip(:,:) * zsnw(:,:)
133      emp_oce  (:,:)   = emp_oce(:,:) - sprecip(:,:) * (1._wp - zsnw(:,:) )
134      qevap_ice(:,:,:) =   0._wp
135      qprec_ice(:,:)   =   rhos * ( sst_m(:,:) * rcpi - rLfus ) * tmask(:,:,1) !  in J/m3
136      qemp_oce (:,:)   = - emp_oce(:,:) * sst_m(:,:) * rcp
137      qemp_ice (:,:)   =   sprecip(:,:) * zsnw * ( sst_m(:,:) * rcpi - rLfus ) * tmask(:,:,1) ! solid precip (only)
138
139      ! total fluxes
140      emp_tot (:,:) = emp_ice  + emp_oce
141      qns_tot (:,:) = at_i_b(:,:) * qns_oce(:,:) + SUM( a_i_b(:,:,:) * qns_ice(:,:,:), dim=3 ) + qemp_ice(:,:) + qemp_oce(:,:)
142      qsr_tot (:,:) = at_i_b(:,:) * qsr_oce(:,:) + SUM( a_i_b(:,:,:) * qsr_ice(:,:,:), dim=3 )
143
144      ! --- shortwave radiation transmitted thru the surface scattering layer (W/m2) --- !
145      qtr_ice_top(:,:,:) = 0._wp
146#endif
147
148   END SUBROUTINE usrdef_sbc_ice_flx
149
150
151   !!======================================================================
152END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.