source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/seasalt.f90 @ 5105

Last change on this file since 5105 was 5105, checked in by abarral, 8 weeks ago

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

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