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.
sbcblk_algo_ice_lu12.F90 in NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC – NEMO

source: NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC/sbcblk_algo_ice_lu12.F90 @ 13830

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

Sea-ice bulk algorithm "AN05" (Andreas et al. 2005) now operational!

File size: 10.0 KB
Line 
1MODULE sbcblk_algo_ice_lu12
2   !!======================================================================
3   !!                   ***  MODULE  sbcblk_algo_ice_lu12  ***
4   !!       Computes turbulent components of surface fluxes over sea-ice
5   !!
6   !!  Lüpkes, C., Gryanik, V. M., Hartmann, J., and Andreas, E. L. ( 2012), A parametrization, based on sea ice morphology,
7   !!  of the neutral atmospheric drag coefficients for weather prediction and climate models, J. Geophys. Res., 117, D13112,
8   !!  doi:10.1029/2012JD017630.
9   !!
10   !!       => Despite the fact that the sea-ice concentration (frice) must be provided,
11   !!          only transfer coefficients, and air temp. + hum. height adjustement
12   !!          over ice are returned/performed.
13   !!        ==> 'frice' is only here to estimate the form drag caused by sea-ice...
14   !!
15   !!       Routine turb_ice_lu12 maintained and developed in AeroBulk
16   !!                     (https://github.com/brodeau/aerobulk/)
17   !!
18   !!            Author: Laurent Brodeau, Summer 2020
19   !!
20   !!----------------------------------------------------------------------
21   USE par_kind, ONLY: wp
22   USE par_oce,  ONLY: jpi, jpj
23   USE phycst          ! physical constants
24   USE sbc_phy         ! Catalog of functions for physical/meteorological parameters in the marine boundary layer
25   USE sbcblk_algo_ice_cdn
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC :: turb_ice_lu12
31
32   REAL(wp), PARAMETER :: rz0_i_s_0  = 0.69e-3_wp  ! Eq.(43) of Lupkes & Gryanik (2015) [m] => to estimate CdN10 for skin drag!
33   REAL(wp), PARAMETER :: rz0_i_f_0  = 4.54e-4_wp  ! bottom p.562 MIZ [m] (LG15)   
34
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE turb_ice_lu12( zt, zu, Ts_i, t_zt, qs_i, q_zt, U_zu, frice, &
39      &                      Cd_i, Ch_i, Ce_i, t_zu_i, q_zu_i,            &
40      &                      CdN, ChN, CeN, xz0, xu_star, xL, xUN10 )
41      !!----------------------------------------------------------------------
42      !!                      ***  ROUTINE  turb_ice_lu12  ***
43      !!
44      !! ** Purpose :   Computes turbulent transfert coefficients of surface
45      !!                fluxes according to:
46      !!                Lüpkes, C., Gryanik, V. M., Hartmann, J., and Andreas, E. L. ( 2012),
47      !!                A parametrization, based on sea ice morphology, of the neutral
48      !!                atmospheric drag coefficients for weather prediction and climate models,
49      !!                J. Geophys. Res., 117, D13112, doi:10.1029/2012JD017630.
50      !!
51      !! INPUT :
52      !! -------
53      !!    *  zt   : height for temperature and spec. hum. of air            [m]
54      !!    *  zu   : height for wind speed (usually 10m)                     [m]
55      !!    *  Ts_i  : surface temperature of sea-ice                         [K]
56      !!    *  t_zt : potential air temperature at zt                         [K]
57      !!    *  qs_i  : saturation specific humidity at temp. Ts_i over ice    [kg/kg]
58      !!    *  q_zt : specific humidity of air at zt                          [kg/kg]
59      !!    *  U_zu : scalar wind speed at zu                                 [m/s]
60      !!    * frice : sea-ice concentration        (fraction)
61      !!
62      !! OUTPUT :
63      !! --------
64      !!    *  Cd_i   : drag coefficient over sea-ice
65      !!    *  Ch_i   : sensible heat coefficient over sea-ice
66      !!    *  Ce_i   : sublimation coefficient over sea-ice
67      !!    *  t_zu_i : pot. air temp. adjusted at zu over sea-ice             [K]
68      !!    *  q_zu_i : spec. hum. of air adjusted at zu over sea-ice          [kg/kg]
69      !!
70      !! OPTIONAL OUTPUT:
71      !! ----------------
72      !!    * CdN     : neutral-stability drag coefficient
73      !!    * ChN     : neutral-stability sensible heat coefficient
74      !!    * CeN     : neutral-stability evaporation coefficient
75      !!    * xz0     : return the aerodynamic roughness length (integration constant for wind stress) [m]
76      !!    * xu_star : return u* the friction velocity                    [m/s]
77      !!    * xL      : return the Obukhov length                          [m]
78      !!    * xUN10   : neutral wind speed at 10m                          [m/s]
79      !!
80      !! ** Author: L. Brodeau, January 2020 / AeroBulk (https://github.com/brodeau/aerobulk/)
81      !!----------------------------------------------------------------------------------
82      REAL(wp), INTENT(in )                     :: zt    ! height for t_zt and q_zt                    [m]
83      REAL(wp), INTENT(in )                     :: zu    ! height for U_zu                             [m]
84      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: Ts_i  ! ice surface temperature                [Kelvin]
85      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: t_zt  ! potential air temperature              [Kelvin]
86      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: qs_i  ! sat. spec. hum. at ice/air interface    [kg/kg]
87      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: q_zt  ! spec. air humidity at zt               [kg/kg]
88      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: U_zu  ! relative wind module at zu                [m/s]
89      REAL(wp), INTENT(in ), DIMENSION(jpi,jpj) :: frice ! sea-ice concentration        (fraction)
90      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) :: Cd_i  ! drag coefficient over sea-ice
91      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) :: Ch_i  ! transfert coefficient for heat over ice
92      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) :: Ce_i  ! transfert coefficient for sublimation over ice
93      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) :: t_zu_i ! pot. air temp. adjusted at zu               [K]
94      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) :: q_zu_i ! spec. humidity adjusted at zu           [kg/kg]
95      !!----------------------------------------------------------------------------------
96      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: CdN
97      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: ChN
98      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: CeN
99      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: xz0  ! Aerodynamic roughness length   [m]
100      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: xu_star  ! u*, friction velocity
101      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: xL  ! zeta (zu/L)
102      REAL(wp), INTENT(out), DIMENSION(jpi,jpj), OPTIONAL :: xUN10  ! Neutral wind at zu
103      !!----------------------------------------------------------------------------------
104      REAL(wp), DIMENSION(:,:), ALLOCATABLE :: dt_zu, dq_zu, z0
105      REAL(wp), DIMENSION(:,:), ALLOCATABLE :: Ubzu
106      !!
107      LOGICAL :: lreturn_cdn=.FALSE., lreturn_chn=.FALSE., lreturn_cen=.FALSE.
108      LOGICAL :: lreturn_z0=.FALSE., lreturn_ustar=.FALSE., lreturn_L=.FALSE., lreturn_UN10=.FALSE.
109      !!
110      CHARACTER(len=40), PARAMETER :: crtnm = 'turb_ice_lu12@sbcblk_algo_ice_lu12.f90'
111      !!----------------------------------------------------------------------------------
112      ALLOCATE ( Ubzu(jpi,jpj) )
113      ALLOCATE ( dt_zu(jpi,jpj), dq_zu(jpi,jpj), z0(jpi,jpj) )
114
115      lreturn_cdn   = PRESENT(CdN)
116      lreturn_chn   = PRESENT(ChN)
117      lreturn_cen   = PRESENT(CeN)
118      lreturn_z0    = PRESENT(xz0)
119      lreturn_ustar = PRESENT(xu_star)
120      lreturn_L     = PRESENT(xL)
121      lreturn_UN10  = PRESENT(xUN10)
122
123      !! Scalar wind speed cannot be below 0.2 m/s
124      Ubzu = MAX( U_zu, wspd_thrshld_ice )
125
126      !! First guess of temperature and humidity at height zu:
127      t_zu_i = MAX( t_zt ,   100._wp )   ! who knows what's given on masked-continental regions...
128      q_zu_i = MAX( q_zt , 0.1e-6_wp )   !               "
129
130      !! Air-Ice & Air-Sea differences (and we don't want them to be 0!)
131      dt_zu = t_zu_i - Ts_i ;   dt_zu = SIGN( MAX(ABS(dt_zu),1.E-6_wp), dt_zu )
132      dq_zu = q_zu_i - qs_i ;   dq_zu = SIGN( MAX(ABS(dq_zu),1.E-9_wp), dq_zu )
133
134      !! To estimate CDN10_skin:
135      !!  we use the method that comes in LG15, i.e. by starting from a default roughness length z0 for skin drag:
136
137      Ce_i(:,:) = rz0_i_s_0 !! temporary array to contain roughness length for skin drag !
138
139
140      !! Method #1:
141      !Cd_i(:,:) = Cd_from_z0( zu, Ce_i(:,:) )  + CdN10_f_LU13( frice(:,:) )
142      !IF( lreturn_cdfrm ) CdN_frm = CdN10_f_LU13( frice(:,:) )
143      !PRINT *, 'LOLO: estimate of Cd_f_i method #1 =>', CdN10_f_LU13( frice(:,:) ); PRINT *, ''
144
145      !! Method #2:
146      !! We need an estimate of z0 over water:
147      !z0_w(:,:) = z0_from_Cd( zu, CD_N10_NCAR(Ubzu) )
148      !!PRINT *, 'LOLO: estimate of z0_w =>', z0_w
149      !Cd_i(:,:)   = Cd_from_z0( zu, Ce_i(:,:) )  + CdN10_f_LU12( frice(:,:), z0_w(:,:) )
150      !IF( lreturn_cdfrm ) CdN_frm =  CdN10_f_LU12( frice(:,:), z0_w(:,:) )
151      !!          N10 skin drag                     N10 form drag
152
153      !! Method #3:
154      !Cd_i(:,:)   = Cd_from_z0( zu, Ce_i(:,:) ) + CdN10_f_LU12_eq36( frice(:,:) )
155      !IF( lreturn_cdfrm ) CdN_frm = CdN10_f_LU12_eq36( frice(:,:) )
156      !PRINT *, 'LOLO: estimate of Cd_f_i method #2 =>', CdN10_f_LU12( frice(:,:), z0_w(:,:) )
157
158      !! Method #4:
159      !! using eq.21 of LG15 instead:
160      z0(:,:) = rz0_i_f_0
161      !Cd_i(:,:)   = Cd_from_z0( zu, Ce_i(:,:) )  + CdN_f_LG15( zu, frice(:,:), z0(:,:) ) / frice(:,:)
162      Cd_i(:,:)   = Cd_from_z0( zu, Ce_i(:,:) )  + CdN_f_LG15( zu, frice(:,:), z0(:,:) ) !/ frice(:,:)
163      !IF( lreturn_cdfrm ) CdN_frm = CdN_f_LG15( zu, frice(:,:), z0(:,:) )
164
165
166      Ch_i(:,:) = Cd_i(:,:)
167      Ce_i(:,:) = Cd_i(:,:)
168
169      IF( lreturn_cdn )   CdN = Cd_i(:,:)
170      IF( lreturn_chn )   ChN = Ch_i(:,:)
171      IF( lreturn_cen )   CeN = Ce_i(:,:)
172
173      IF( lreturn_z0 )    xz0     = z0_from_Cd( zu, Cd_i )
174      IF( lreturn_ustar ) xu_star = SQRT(Cd_i)*Ubzu
175      IF( lreturn_L )     xL      = 1./One_on_L(t_zu_i, q_zu_i, SQRT(Cd_i)*Ubzu, &
176         &                          Cd_i/SQRT(Cd_i)*dt_zu, Cd_i/SQRT(Cd_i)*dq_zu)
177      IF( lreturn_UN10 )  xUN10   = SQRT(Cd_i)*Ubzu/vkarmn * LOG( 10._wp / z0_from_Cd( zu, Cd_i ) )
178
179      DEALLOCATE ( dt_zu, dq_zu, z0 )
180      DEALLOCATE ( Ubzu )
181
182   END SUBROUTINE turb_ice_lu12
183
184   !!======================================================================
185END MODULE sbcblk_algo_ice_lu12
Note: See TracBrowser for help on using the repository browser.