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

Last change on this file since 5277 was 5274, checked in by abarral, 9 hours ago

Replace yomcst.h by existing module

File size: 2.4 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  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
8USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
9          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
10          , R_ecc, R_peri, R_incl                                      &
11          , RA, RG, R1SA                                         &
12          , RSIGMA                                                     &
13          , R, RMD, RMV, RD, RV, RCPD                    &
14          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
15          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
16          , RCW, RCS                                                 &
17          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
18          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
19          , RALPD, RBETD, RGAMD
20IMPLICIT NONE
21  !
22
23  INCLUDE "chem.h"
24  INCLUDE "chem_spla.h"
25
26  INCLUDE "YOECUMF.h"
27  !
28  INTEGER :: i, bin                 !local variables
29  REAL :: pct_ocean(klon)           !hfraction of Ocean in each grid
30  REAL :: v_10m(klon), u_10m(klon)  !V&H components of wind @10 m
31  REAL :: w_speed_10m(klon)         !wind speed at 10m from surface
32  REAL :: lmt_sea_salt(klon,ss_bins)!sea salt emission flux - mg/m2/s
33  REAL :: sea_salt_flux(ss_bins)    !sea salt emission flux per unit wind speed
34
35  REAL :: wind, ocean
36  !
37  !------Sea salt emission fluxes for each size bin calculated
38  !------based on on parameterisation of Gong et al. (1997).
39  !------Fluxes of sea salt for each size bin are given in mg/m^2/sec
40  !------at wind speed of 1 m/s at 10m height (at 80% RH).
41  !------Fluxes at various wind speeds (@10 m from sea
42  !------surfaces are estimated using relationship: F=flux*U_10^3.14
43  !
44  !nhl for size bin of 0.03-0.5 and 0.5-20
45  DATA sea_salt_flux/4.5E-09,8.7E-7/
46
47  DO i=1, klon
48  w_speed_10m(i)= (v_10m(i)**2.0+u_10m(i)**2.0)**0.5
49  ENDDO
50  !
51  DO bin=1,ss_bins
52  wind=0.0
53  ocean=0.0
54  DO i=1, klon
55  lmt_sea_salt(i,bin)=sea_salt_flux(bin)*(w_speed_10m(i)**3.41) &
56        *pct_ocean(i)*1.e-4*1.e-3                       !g/cm2/s
57  wind=wind+w_speed_10m(i)
58  ocean=ocean+pct_ocean(i)
59  ENDDO
60   ! print *,'Sea Salt flux = ',sea_salt_flux(bin)
61  ENDDO
62   ! print *,'SUM OF WIND = ',wind
63   ! print *,'SUM OF OCEAN SURFACE = ',ocean
64  RETURN
65END SUBROUTINE seasalt
Note: See TracBrowser for help on using the repository browser.