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/ICE_AGRIF/MY_SRC – NEMO

source: NEMO/trunk/tests/ICE_AGRIF/MY_SRC/usrdef_sbc.F90 @ 14072

Last change on this file since 14072 was 14072, checked in by laurent, 3 years ago

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

  • Property svn:keywords set to Id
File size: 7.6 KB
Line 
1MODULE usrdef_sbc
2   !!======================================================================
3   !!                       ***  MODULE  usrdef_sbc  ***
4   !!
5   !!                      ===  ICE_AGRIF 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 ICE_AGRIF 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 phycst          ! physical constants
20   USE ice, ONLY       : at_i_b, a_i_b
21   USE icethd_dh       ! for CALL ice_thd_snwblow
22   USE sbc_phy, ONLY : pp_cldf
23   !
24   USE in_out_manager  ! I/O manager
25   USE lib_mpp         ! distribued memory computing library
26   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
27   USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   usrdef_sbc_oce      ! routine called by sbcmod.F90 for sbc ocean
33   PUBLIC   usrdef_sbc_ice_tau  ! routine called by icestp.F90 for ice dynamics
34   PUBLIC   usrdef_sbc_ice_flx  ! routine called by icestp.F90 for ice thermo
35
36   !!----------------------------------------------------------------------
37   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
38   !! $Id$
39   !! Software governed by the CeCILL license (see ./LICENSE)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE usrdef_sbc_oce( kt, Kbb )
44      !!---------------------------------------------------------------------
45      !!                    ***  ROUTINE usr_def_sbc  ***
46      !!             
47      !! ** Purpose :   provide at each time-step the surface boundary
48      !!              condition, i.e. the momentum, heat and freshwater fluxes.
49      !!
50      !! ** Method  :   all 0 fields, for ICE_AGRIF case
51      !!                CAUTION : never mask the surface stress field !
52      !!
53      !! ** Action  : - set to ZERO all the ocean surface boundary condition, i.e.   
54      !!                   utau, vtau, taum, wndm, qns, qsr, emp, sfx
55      !!
56      !!----------------------------------------------------------------------
57      INTEGER, INTENT(in) ::   kt   ! ocean time step
58      INTEGER, INTENT(in) ::   Kbb  ! ocean time index
59      !!---------------------------------------------------------------------
60      !
61      IF( kt == nit000 ) THEN
62         !
63         IF(lwp)   WRITE(numout,*)' usrdef_sbc_oce : ICE_AGRIF case: NO surface forcing'
64         ! --- oce variables --- !
65         utau(:,:) = 0._wp 
66         vtau(:,:) = 0._wp
67         taum(:,:) = 0._wp
68         wndm(:,:) = 0._wp
69         !
70         emp (:,:) = 0._wp
71         sfx (:,:) = 0._wp
72         qns (:,:) = 0._wp
73         qsr (:,:) = 0._wp
74         !
75         utau_b(:,:) = 0._wp 
76         vtau_b(:,:) = 0._wp
77         emp_b (:,:) = 0._wp
78         sfx_b (:,:) = 0._wp
79         qns_b (:,:) = 0._wp
80         !
81      ENDIF
82      !
83   END SUBROUTINE usrdef_sbc_oce
84
85   SUBROUTINE usrdef_sbc_ice_tau( kt )
86      !!---------------------------------------------------------------------
87      !!                     ***  ROUTINE usrdef_sbc_ice_tau  ***
88      !!
89      !! ** Purpose :   provide the surface boundary (momentum) condition over sea-ice
90      !!---------------------------------------------------------------------
91      INTEGER, INTENT(in) ::   kt   ! ocean time step
92      !!---------------------------------------------------------------------
93      IF( kt==nit000 .AND. lwp)   WRITE(numout,*)' usrdef_sbc_ice : ICE_AGRIF case: constant stress forcing'
94      !
95      utau_ice(:,:) = 1.3_wp   ! <=> 0.5 m/s
96      vtau_ice(:,:) = 0._wp
97      !
98   END SUBROUTINE usrdef_sbc_ice_tau
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      INTEGER  ::   jl
111      REAL(wp) ::   zfr1, zfr2                 ! local variables
112      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw   ! snw distribution after wind blowing
113      REAL(wp), DIMENSION(jpi,jpj) ::   ztri
114      !!---------------------------------------------------------------------
115      !
116      IF( kt==nit000 .AND. lwp)   WRITE(numout,*)' usrdef_sbc_ice : ICE_AGRIF case: NO flux forcing'
117      !
118      ! ocean variables (renaming)
119      emp_oce (:,:)   = 0._wp   ! uniform value for freshwater budget (E-P)
120      qsr_oce (:,:)   = 0._wp   ! uniform value for     solar radiation
121      qns_oce (:,:)   = 0._wp   ! uniform value for non-solar radiation
122
123      ! ice variables
124      alb_ice (:,:,:) = 0.7_wp  ! useless
125      qsr_ice (:,:,:) = 0._wp   ! uniform value for     solar radiation
126      qns_ice (:,:,:) = 0._wp   ! uniform value for non-solar radiation
127      sprecip (:,:)   = 0._wp   ! uniform value for snow precip
128      evap_ice(:,:,:) = 0._wp   ! uniform value for sublimation
129
130      ! ice fields deduced from above
131      zsnw(:,:) = 1._wp
132      !!CALL lim_thd_snwblow( at_i_b, zsnw )  ! snow distribution over ice after wind blowing
133      emp_ice  (:,:)   = SUM( a_i_b(:,:,:) * evap_ice(:,:,:), dim=3 ) - sprecip(:,:) * zsnw(:,:)
134      emp_oce  (:,:)   = emp_oce(:,:) - sprecip(:,:) * (1._wp - zsnw(:,:) )
135      qevap_ice(:,:,:) =   0._wp
136      qprec_ice(:,:)   =   rhos * ( sst_m(:,:) * rcpi - rLfus ) * tmask(:,:,1) !  in J/m3
137      qemp_oce (:,:)   = - emp_oce(:,:) * sst_m(:,:) * rcp
138      qemp_ice (:,:)   =   sprecip(:,:) * zsnw * ( sst_m(:,:) * rcpi - rLfus ) * tmask(:,:,1) ! solid precip (only)
139
140      ! total fluxes
141      emp_tot (:,:) = emp_ice  + emp_oce
142      qns_tot (:,:) = at_i_b(:,:) * qns_oce(:,:) + SUM( a_i_b(:,:,:) * qns_ice(:,:,:), dim=3 ) + qemp_ice(:,:) + qemp_oce(:,:)
143      qsr_tot (:,:) = at_i_b(:,:) * qsr_oce(:,:) + SUM( a_i_b(:,:,:) * qsr_ice(:,:,:), dim=3 )
144
145      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- !
146      cloud_fra(:,:) = pp_cldf
147      ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm
148      !
149      DO jl = 1, jpl
150         WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )     ! linear decrease from hi=0 to 10cm 
151            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) )
152         ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )     ! constant (ztri) when hi>10cm
153            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:)
154         ELSEWHERE                                                         ! zero when hs>0
155            qtr_ice_top(:,:,jl) = 0._wp
156         END WHERE
157      ENDDO
158         
159   END SUBROUTINE usrdef_sbc_ice_flx
160
161
162   !!======================================================================
163END MODULE usrdef_sbc
Note: See TracBrowser for help on using the repository browser.