source: LMDZ6/trunk/libf/phylmd/Dust/seasalt.f90 @ 5354

Last change on this file since 5354 was 5337, checked in by Laurent Fairhead, 3 weeks ago

Getting rid of dependance to dynamics

File size: 1.6 KB
Line 
1  ! This subroutine estimateis Sea Salt emission fluxes over
2  ! Oceanic surfaces.
3!
4SUBROUTINE seasalt(v_10m, u_10m, pct_ocean, lmt_sea_salt)
5
6USE chem_spla_mod_h
7  USE chem_mod_h
8  USE yoecumf_mod_h
9    USE dimphy
10USE yomcst_mod_h
11IMPLICIT NONE
12  !
13
14
15  !
16  INTEGER :: i, bin                 !local variables
17  REAL :: pct_ocean(klon)           !hfraction of Ocean in each grid
18  REAL :: v_10m(klon), u_10m(klon)  !V&H components of wind @10 m
19  REAL :: w_speed_10m(klon)         !wind speed at 10m from surface
20  REAL :: lmt_sea_salt(klon,ss_bins)!sea salt emission flux - mg/m2/s
21  REAL :: sea_salt_flux(ss_bins)    !sea salt emission flux per unit wind speed
22
23  REAL :: wind, ocean
24  !
25  !------Sea salt emission fluxes for each size bin calculated
26  !------based on on parameterisation of Gong et al. (1997).
27  !------Fluxes of sea salt for each size bin are given in mg/m^2/sec
28  !------at wind speed of 1 m/s at 10m height (at 80% RH).
29  !------Fluxes at various wind speeds (@10 m from sea
30  !------surfaces are estimated using relationship: F=flux*U_10^3.14
31  !
32  !nhl for size bin of 0.03-0.5 and 0.5-20
33  DATA sea_salt_flux/4.5E-09,8.7E-7/
34
35  DO i=1, klon
36  w_speed_10m(i)= (v_10m(i)**2.0+u_10m(i)**2.0)**0.5
37  ENDDO
38  !
39  DO bin=1,ss_bins
40  wind=0.0
41  ocean=0.0
42  DO i=1, klon
43  lmt_sea_salt(i,bin)=sea_salt_flux(bin)*(w_speed_10m(i)**3.41) &
44        *pct_ocean(i)*1.e-4*1.e-3                       !g/cm2/s
45  wind=wind+w_speed_10m(i)
46  ocean=ocean+pct_ocean(i)
47  ENDDO
48   ! print *,'Sea Salt flux = ',sea_salt_flux(bin)
49  ENDDO
50   ! print *,'SUM OF WIND = ',wind
51   ! print *,'SUM OF OCEAN SURFACE = ',ocean
52  RETURN
53END SUBROUTINE seasalt
Note: See TracBrowser for help on using the repository browser.