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

Put .h into modules

File:
1 moved

Legend:

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

    r5159 r5160  
    1 ! This SUBROUTINE estimateis Sea Salt emission fluxes over
    2 ! Oceanic surfaces.
     1MODULE lmdz_seasalt
     2  IMPLICIT NONE; PRIVATE
     3  PUBLIC seasalt
     4CONTAINS
     5  ! This SUBROUTINE estimates Sea Salt emission fluxes over Oceanic surfaces.
     6  SUBROUTINE seasalt(v_10m, u_10m, pct_ocean, lmt_sea_salt)
     7    USE dimphy
     8    USE lmdz_YOECUMF
     9    USE lmdz_yomcst
     10    USE lmdz_chem_spla, ONLY: ss_bins
    311
    4 SUBROUTINE seasalt(v_10m, u_10m, pct_ocean, lmt_sea_salt)
     12    IMPLICIT NONE
    513
    6   USE dimphy
    7   USE lmdz_YOECUMF
    8   USE lmdz_yomcst
     14    INTEGER :: i, bin                 !local variables
     15    REAL :: pct_ocean(klon)           !hfraction of Ocean in each grid
     16    REAL :: v_10m(klon), u_10m(klon)  !V&H components of wind @10 m
     17    REAL :: w_speed_10m(klon)         !wind speed at 10m from surface
     18    REAL :: lmt_sea_salt(klon, ss_bins)!sea salt emission flux - mg/m2/s
     19    REAL :: sea_salt_flux(ss_bins)    !sea salt emission flux per unit wind speed
    920
    10 USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
    11   IMPLICIT NONE
    12   !
     21    REAL :: wind, ocean
    1322
    14   INCLUDE "chem.h"
    15   INCLUDE "chem_spla.h"
     23    !------Sea salt emission fluxes for each size bin calculated
     24    !------based on on parameterisation of Gong et al. (1997).
     25    !------Fluxes of sea salt for each size bin are given in mg/m^2/sec
     26    !------at wind speed of 1 m/s at 10m height (at 80% RH).
     27    !------Fluxes at various wind speeds (@10 m from sea
     28    !------surfaces are estimated using relationship: F=flux*U_10^3.14
    1629
    17   INTEGER :: i, bin                 !local variables
    18   REAL :: pct_ocean(klon)           !hfraction of Ocean in each grid
    19   REAL :: v_10m(klon), u_10m(klon)  !V&H components of wind @10 m
    20   REAL :: w_speed_10m(klon)         !wind speed at 10m from surface
    21   REAL :: lmt_sea_salt(klon, ss_bins)!sea salt emission flux - mg/m2/s
    22   REAL :: sea_salt_flux(ss_bins)    !sea salt emission flux per unit wind speed
     30    !nhl for size bin of 0.03-0.5 and 0.5-20
     31    DATA sea_salt_flux/4.5E-09, 8.7E-7/
    2332
    24   REAL :: wind, ocean
     33    DO i = 1, klon
     34      w_speed_10m(i) = (v_10m(i)**2.0 + u_10m(i)**2.0)**0.5
     35    ENDDO
    2536
    26   !------Sea salt emission fluxes for each size bin calculated
    27   !------based on on parameterisation of Gong et al. (1997).
    28   !------Fluxes of sea salt for each size bin are given in mg/m^2/sec
    29   !------at wind speed of 1 m/s at 10m height (at 80% RH).
    30   !------Fluxes at various wind speeds (@10 m from sea
    31   !------surfaces are estimated using relationship: F=flux*U_10^3.14
     37    DO bin = 1, ss_bins
     38      wind = 0.0
     39      ocean = 0.0
     40      DO i = 1, klon
     41        lmt_sea_salt(i, bin) = sea_salt_flux(bin) * (w_speed_10m(i)**3.41) &
     42                * pct_ocean(i) * 1.e-4 * 1.e-3                       !g/cm2/s
     43        wind = wind + w_speed_10m(i)
     44        ocean = ocean + pct_ocean(i)
     45      ENDDO
     46      ! PRINT *,'Sea Salt flux = ',sea_salt_flux(bin)
     47    ENDDO
     48    ! PRINT *,'SUM OF WIND = ',wind
     49    ! PRINT *,'SUM OF OCEAN SURFACE = ',ocean
    3250
    33   !nhl for size bin of 0.03-0.5 and 0.5-20
    34   DATA sea_salt_flux/4.5E-09, 8.7E-7/
    35 
    36   DO i = 1, klon
    37     w_speed_10m(i) = (v_10m(i)**2.0 + u_10m(i)**2.0)**0.5
    38   ENDDO
    39 
    40   DO bin = 1, ss_bins
    41     wind = 0.0
    42     ocean = 0.0
    43     DO i = 1, klon
    44       lmt_sea_salt(i, bin) = sea_salt_flux(bin) * (w_speed_10m(i)**3.41) &
    45               * pct_ocean(i) * 1.e-4 * 1.e-3                       !g/cm2/s
    46       wind = wind + w_speed_10m(i)
    47       ocean = ocean + pct_ocean(i)
    48     ENDDO
    49     ! print *,'Sea Salt flux = ',sea_salt_flux(bin)
    50   ENDDO
    51   ! print *,'SUM OF WIND = ',wind
    52   ! print *,'SUM OF OCEAN SURFACE = ',ocean
    53 
    54 END SUBROUTINE seasalt
     51  END SUBROUTINE seasalt
     52END MODULE lmdz_seasalt
Note: See TracChangeset for help on using the changeset viewer.