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

source: NEMO/trunk/tests/ICE_ADV1D/MY_SRC/usrdef_sbc.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

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