Changeset 4763 for LMDZ6


Ignore:
Timestamp:
Dec 10, 2023, 10:37:06 PM (6 months ago)
Author:
lguez
Message:

Polish

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/StratAer/strataer_emiss_mod.F90

    r4625 r4763  
    11MODULE strataer_emiss_mod
    2 ! This module contains information about strato microphysic model emission parameters
    3  
     2  ! This module contains information about strato microphysic model emission parameters
     3
    44CONTAINS
    5    
     5
    66  SUBROUTINE strataer_emiss_init()
    7    
     7
    88    USE strataer_local_var_mod
    99    USE ioipsl_getin_p_mod, ONLY : getin_p
    1010    USE print_control_mod, ONLY : lunout
    1111    USE mod_phys_lmdz_para, ONLY : is_master
    12    
     12
    1313    ! Local variables
    1414    INTEGER                  :: ispec
    15    
     15
    1616    WRITE(lunout,*) 'IN STRATAER_EMISS INIT WELCOME!'
    17    
     17
    1818    IF (flag_emit.EQ.1 .OR. flag_emit.EQ.4) THEN ! Volcano
    1919       CALL getin_p('nErupt',nErupt) !eruption nb
    2020       CALL getin_p('injdur',injdur) !injection duration
    21        
     21
    2222       IF (flag_emit==1) THEN
    2323          CALL getin_p('nAerErupt', nAerErupt) !sulfur aer nb
     
    2525          CALL getin_p('nSpeciesErupt', nSpeciesErupt) !chimical species nb
    2626       ENDIF
    27        
     27
    2828       IF (nErupt.GT.0) THEN
    2929          ALLOCATE(year_emit_vol(nErupt),mth_emit_vol(nErupt),day_emit_vol(nErupt))
     
    3737                ALLOCATE(m_H2O_emiss_vol(nErupt))
    3838                ALLOCATE(m_H2O_emiss_vol_daily(nErupt))
    39 !                ALLOCATE(d_q_emiss(klon,klev))
     39                !                ALLOCATE(d_q_emiss(klon,klev))
    4040                ALLOCATE(budg_emi(klon,nAerErupt+1))
    4141                m_H2O_emiss_vol(:)=0.
    4242                m_H2O_emiss_vol_daily(:)=0.
    43 !                d_q_emiss(:,:)=0.
     43                !                d_q_emiss(:,:)=0.
    4444             ELSE
    4545                ALLOCATE(budg_emi(klon,nAerErupt))
     
    4848          ELSEIF (flag_emit==4) THEN
    4949             ALLOCATE(m_Chlore_emiss_vol(nErupt))
    50              ALLOCATE(id_HCl) 
     50             ALLOCATE(id_HCl)
    5151             ALLOCATE(m_Brome_emiss_vol(nErupt))
    5252             ALLOCATE(id_HBr)
     
    6565               'No eruption define in physiq_def (nErupt=0). Add at one eruption or use background condition.',1)
    6666       ENDIF ! fin if nerupt
    67        
     67
    6868       ! injection params (dates, loc, injections params)
    6969       CALL getin_p('year_emit_vol',year_emit_vol)
     
    7878       IF (flag_emit==1) THEN
    7979          CALL getin_p('m_sulf_emiss_vol',m_sulf_emiss_vol)
    80         if (ok_qemiss) then
    81          CALL getin_p('m_H2O_emiss_vol',m_H2O_emiss_vol)
    82         endif
     80          if (ok_qemiss) then
     81             CALL getin_p('m_H2O_emiss_vol',m_H2O_emiss_vol)
     82          endif
    8383       ELSEIF (flag_emit==4) THEN
    8484          CALL getin_p('id_species',id_species)
    85           CALL getin_p('m_Chlore_emiss_vol',m_Chlore_emiss_vol) 
     85          CALL getin_p('m_Chlore_emiss_vol',m_Chlore_emiss_vol)
    8686          CALL getin_p('id_HCl',id_HCl)
    8787          CALL getin_p('m_Brome_emiss_vol',m_Brome_emiss_vol)
     
    9292          CALL getin_p('id_H2O',id_H2O)
    9393       ENDIF
    94        
     94
    9595    ELSEIF (flag_emit == 2) THEN ! SAI
    9696       CALL getin_p('m_aer_emiss_sai',m_aer_emiss_sai)
     
    105105       CALL getin_p('day_emit_sai_start',day_emit_sai_start)
    106106       CALL getin_p('day_emit_sai_end',day_emit_sai_end)
    107        
     107
    108108    ELSEIF (flag_emit == 3) THEN ! SAI between latitudes
    109109       CALL getin_p('m_aer_emiss_sai',m_aer_emiss_sai)
     
    114114       CALL getin_p('xlat_min_sai',xlat_min_sai)
    115115    ENDIF
    116    
     116
    117117    IF (flag_emit == 1) THEN
    118118       DO ispec=1,nAerErupt
     
    124124             m_species_emiss_vol(:,ispec) = m_Chlore_emiss_vol(:)
    125125          ENDIF
    126           IF (id_species(ispec) == id_HBr) THEN 
     126          IF (id_species(ispec) == id_HBr) THEN
    127127             m_species_emiss_vol(:,ispec) = m_Brome_emiss_vol(:)
    128128          ENDIF
     
    135135       ENDDO
    136136    ENDIF
    137    
     137
    138138    !============= Injection ponderation =============
    139139    IF (flag_emit > 0) THEN
     
    141141       WRITE(lunout,*) 'IN STRATAER INIT : ponde_lonlat_vol',ponde_lonlat_vol
    142142    ENDIF
    143    
     143
    144144    !============= Print params =============
    145145    IF (is_master) THEN
     
    148148          WRITE(lunout,*) 'IN STRATAER injdur: ',injdur
    149149          WRITE(lunout,*) 'IN STRATAER nAerErupt: ',nAerErupt
    150          
     150
    151151          WRITE(lunout,*) 'IN STRATAER : year_emit_vol',year_emit_vol
    152152          WRITE(lunout,*) 'IN STRATAER : mth_emit_vol',mth_emit_vol
     
    195195       ENDIF
    196196    ENDIF ! if master
    197    
     197
    198198    WRITE(lunout,*) 'IN STRATAER_EMISS END'
    199199  END SUBROUTINE strataer_emiss_init
    200  
     200
    201201  ! Compute the ponderation to applicate in each grid point for all eruptions and init
    202202  ! dlat & dlon variables
    203203  SUBROUTINE strataer_ponde_init()
    204    
     204
    205205    USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    206206    USE dimphy, ONLY: klon
     
    208208    USE print_control_mod, ONLY : lunout
    209209    USE strataer_local_var_mod
    210    
     210
    211211    INCLUDE "YOMCST.h"  !--RPI
    212    
     212
    213213    ! local var
    214214    REAL                :: lat_reg_deg,lon_reg_deg ! lat and lon of grid points in degree
    215215    INTEGER             :: ieru, i, j
    216    
     216
    217217    ALLOCATE(ponde_lonlat_vol(nErupt))
    218    
     218
    219219    !Compute lon/lat ponderation for injection
    220220    dlat=180./2./FLOAT(nbp_lat)   ! d latitude in degree
     
    224224    WRITE(lunout,*) 'IN STRATAER_INIT xlat_min=',xlat_min_vol,'xlat_max=',xlat_max_vol
    225225    WRITE(lunout,*) 'IN STRATAER_INIT xlon_min=',xlon_min_vol,'xlon_max=',xlon_max_vol
    226    
     226
    227227    DO ieru=1, nErupt
    228228       ponde_lonlat_vol(ieru) = 0
     
    241241       ENDIF
    242242    ENDDO !ieru
    243    
     243
    244244    WRITE(lunout,*) 'IN STRATAER_PONDE_INIT ponde_lonlat: ', ponde_lonlat_vol
    245    
     245
    246246  END SUBROUTINE strataer_ponde_init
    247  
     247
    248248END MODULE strataer_emiss_mod
Note: See TracChangeset for help on using the changeset viewer.