Ignore:
Timestamp:
Aug 2, 2024, 9:58:25 PM (7 weeks ago)
Author:
abarral
Message:

Put dimensions.h and paramet.h into modules

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/seasalt.f90

    r5144 r5159  
    11! This SUBROUTINE estimateis Sea Salt emission fluxes over
    22! Oceanic surfaces.
    3 !
     3
    44SUBROUTINE seasalt(v_10m, u_10m, pct_ocean, lmt_sea_salt)
    55
     
    88  USE lmdz_yomcst
    99
     10USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
    1011  IMPLICIT NONE
    1112  !
    12   INCLUDE "dimensions.h"
     13
    1314  INCLUDE "chem.h"
    1415  INCLUDE "chem_spla.h"
    15   !
     16
    1617  INTEGER :: i, bin                 !local variables
    1718  REAL :: pct_ocean(klon)           !hfraction of Ocean in each grid
     
    2223
    2324  REAL :: wind, ocean
    24   !
     25
    2526  !------Sea salt emission fluxes for each size bin calculated
    2627  !------based on on parameterisation of Gong et al. (1997).
     
    2930  !------Fluxes at various wind speeds (@10 m from sea
    3031  !------surfaces are estimated using relationship: F=flux*U_10^3.14
    31   !
     32
    3233  !nhl for size bin of 0.03-0.5 and 0.5-20
    3334  DATA sea_salt_flux/4.5E-09, 8.7E-7/
     
    3637    w_speed_10m(i) = (v_10m(i)**2.0 + u_10m(i)**2.0)**0.5
    3738  ENDDO
    38   !
     39
    3940  DO bin = 1, ss_bins
    4041    wind = 0.0
Note: See TracChangeset for help on using the changeset viewer.