Ignore:
Timestamp:
Jan 31, 2024, 4:36:51 PM (10 months ago)
Author:
afalco
Message:

Pluto PCM:
Imported condense n2 from pluto.old.
Aerosol data from Pluto.old not yet working.
AF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/radii_mod.F90

    r3184 r3195  
    44!  module to centralize the radii calculations for aerosols
    55!==================================================================
    6      
     6
    77!     N2 cloud properties (initialized in inifis)
    88      real,save :: Nmix_n2 ! Number mixing ratio of N2 ice particles
     
    2121!     Purpose
    2222!     -------
    23 !     Compute the effective radii of liquid and icy water particles
    24 !     Jeremy Leconte (2012)
    25 !     Extended to dust, N2, NH3, 2-lay,Nlay,auroral aerosols by ??
    26 !     Added Radiative Generic Condensable Species effective radii
    27 !     calculations  (Lucas Teinturier 2022)
     23!     Compute the effective radii of haze particles  (TB)
    2824!
    29 !     Authors
    30 !     -------
    31 !     Jeremy Leconte (2012)
    3225!
    3326!==================================================================
     
    3528      use ioipsl_getin_p_mod, only: getin_p
    3629      use radinc_h, only: naerkind
    37       use aerosol_mod, only: iaero_back2lay, iaero_n2, iaero_dust, &
    38                              iaero_h2so4, iaero_nh3, iaero_nlay, &
    39                              iaero_aurora, iaero_generic, i_rgcs_ice
    40       use callkeys_mod, only: size_nh3_cloud, nlayaero, aeronlay_size, &
     30      use aerosol_mod, only: iaero_haze, i_haze, &
     31                              iaero_generic, i_rgcs_ice
     32      use callkeys_mod, only: nlayaero, aeronlay_size, &
    4133                              aeronlay_nueff,aerogeneric
    42       use tracer_h, only: radius, nqtot, is_rgcs
     34      use tracer_h, only: radius, nqtot, is_rgcs, nmono
    4335      Implicit none
    4436
     
    4739
    4840      real, intent(out) :: reffrad(ngrid,nlayer,naerkind)      !aerosols radii (K)
    49       real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !variance     
     41      real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !variance
    5042
    51       logical, save :: firstcall=.true.
    52 !$OMP THREADPRIVATE(firstcall)
    53       integer :: iaer, ia , iq, i_rad 
     43      integer :: iaer, ia , iq, i_rad
    5444
    5545      do iaer=1,naerkind
    56 !     these values will change once the microphysics gets to work
    57 !     UNLESS tracer=.false., in which case we should be working with
    58 !     a fixed aerosol layer, and be able to define reffrad in a
    59 !     .def file. To be improved!
    60 !                |-> Done in th n-layer aerosol case (JVO 20)
    61 
    62          if(iaer.eq.iaero_n2)then ! N2 ice
    63             reffrad(1:ngrid,1:nlayer,iaer) = 1.e-4
    64             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
     46         print*, 'TB22 iaer',iaer,iaero_haze
     47         if(iaer.eq.iaero_haze)then
     48           ! Equivalent sphere radius
     49           reffrad(1:ngrid,1:nlayer,iaer)=radius(i_haze)*nmono**(1./3.)
     50           !reffrad(1:ngrid,1:nlayer,iaer) = 2.e-6 ! haze
     51           nueffrad(1:ngrid,1:nlayer,iaer) = 0.02 ! haze
     52           print*, 'TB22 Hello2',radius(i_haze)*nmono**(1./3.)
    6553         endif
    66 
    67          if(iaer.eq.iaero_dust)then ! dust
    68             reffrad(1:ngrid,1:nlayer,iaer) = 1.e-5
    69             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    70          endif
    71  
    72          if(iaer.eq.iaero_h2so4)then ! H2SO4 ice
    73             reffrad(1:ngrid,1:nlayer,iaer) = 1.e-6
    74             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    75          endif
    76            
    77          if(iaer.eq.iaero_back2lay)then ! Two-layer aerosols
    78             reffrad(1:ngrid,1:nlayer,iaer) = 2.e-6
    79             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    80          endif
    81 
    82 
    83          if(iaer.eq.iaero_nh3)then ! Nh3 cloud
    84             reffrad(1:ngrid,1:nlayer,iaer) = size_nh3_cloud
    85             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    86          endif
    87 
    88          do ia=1,nlayaero
    89             if(iaer.eq.iaero_nlay(ia))then ! N-layer aerosols
    90                reffrad(1:ngrid,1:nlayer,iaer) = aeronlay_size(ia)
    91                nueffrad(1:ngrid,1:nlayer,iaer) = aeronlay_nueff(ia)
    92             endif
    93          enddo
    94 
    95          if(iaer.eq.iaero_aurora)then ! Auroral aerosols
    96             reffrad(1:ngrid,1:nlayer,iaer) = 3.e-7
    97             nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    98          endif
    99 
    100          do ia=1,aerogeneric     ! Radiative Generic Condensable Species
    101             if (iaer .eq. iaero_generic(ia)) then
    102                i_rad = i_rgcs_ice(ia)
    103                reffrad(1:ngrid,1:nlayer,iaer)=radius(i_rad)
    104                nueffrad(1:ngrid,1:nlayer,iaer) = 0.1
    105             endif
    106          enddo  ! generic radiative condensable aerosols
    107          
    108       enddo ! iaer=1,naerkind
     54      enddo
    10955
    11056   end subroutine su_aer_radii
     
    11359
    11460!==================================================================
    115    subroutine n2_reffrad(ngrid,nlayer,nq,pq,reffrad)
    116 !==================================================================
     61   subroutine haze_reffrad_fix(ngrid,nlayer,zzlay,reffrad,nueffrad)
     62      !==================================================================
    11763!     Purpose
    11864!     -------
    119 !     Compute the effective radii of n2 ice particles !AF24: copied from CO2
    120 !
    121 !     Authors
    122 !     -------
    123 !     Jeremy Leconte (2012)
     65!     Compute the effective radii of haze particles
     66!     fixed profile of radius (TB)
    12467!
    12568!==================================================================
    126       USE tracer_h, only:igcm_n2_ice,rho_n2
     69      use radinc_h, only: naerkind
     70      USE tracer_h, only:rho_n2,nmono
    12771      use comcstfi_mod, only: pi
     72      use aerosol_mod, only: iaero_haze, i_haze
     73      use datafile_mod
    12874      Implicit none
    12975
    130       integer,intent(in) :: ngrid,nlayer,nq
     76      integer,intent(in) :: ngrid,nlayer
     77      real,intent(in) :: zzlay(ngrid,nlayer)
     78      real, intent(out) :: reffrad(ngrid,nlayer,naerkind)      ! haze particles radii (m)
     79      real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !
    13180
    132       real, intent(in) :: pq(ngrid,nlayer,nq) !tracer mixing ratios (kg/kg)
    133       real, intent(out) :: reffrad(ngrid,nlayer)      !n2 ice particles radii (m)
     81      real :: zrad
     82      real,external :: CBRT
    13483
    135       integer :: ig,l
    136       real :: zrad   
    137       real,external :: CBRT           
    138            
    139      
     84      logical, save :: firstcall=.true.
     85      !$OMP THREADPRIVATE(firstcall)
    14086
    141       if (radfixed) then
    142          reffrad(1:ngrid,1:nlayer) = 5.e-5 ! N2 ice
    143       else
    144          do l=1,nlayer
    145             do ig=1,ngrid
    146                zrad = CBRT( 3*pq(ig,l,igcm_n2_ice)/(4*Nmix_n2*pi*rho_n2) )
    147                reffrad(ig,l) = min(max(zrad,1.e-6),100.e-6)
    148             enddo
    149          enddo     
    150       end if
     87!     Local variables
     88      integer :: iaer,l,ifine,ig
     89      real :: radvec(ngrid,nlayer)
    15190
    152    end subroutine n2_reffrad
     91      !!read altitudes and radius
     92      integer Nfine
     93      !parameter(Nfine=21)
     94      parameter(Nfine=701)
     95      character(len=100) :: file_path
     96      real,save :: levdat(Nfine),raddat(Nfine)
     97
     98!---------------- INPUT ------------------------------------------------
     99
     100      IF (firstcall) then
     101         firstcall=.false.
     102         file_path=trim(datadir)//'/haze_prop/hazerad.txt'
     103         open(223,file=file_path,form='formatted')
     104         do ifine=1,Nfine
     105            read(223,*) levdat(ifine), raddat(ifine)
     106         enddo
     107         close(223)
     108         print*, 'TB22 READ HAZERAD'
     109       ENDIF
     110
     111       ! in radii mod levs has been put in km
     112       DO ig=1,ngrid
     113         CALL interp_line(levdat,raddat,Nfine,zzlay(ig,:)/1000,radvec(ig,:),nlayer)
     114       enddo
     115
     116       do iaer=1,naerkind
     117             if(iaer.eq.iaero_haze)then
     118                  ! spherical radius or eq spherical radius
     119                  ! TB22: fractal has no impact on reffrad if haze_radproffix
     120                  do ig=1,ngrid
     121                     do l=1,nlayer
     122                        reffrad(ig,l,iaer)=radvec(ig,l)*1.e-9    !  nm => m
     123                     enddo
     124                  enddo
     125                  nueffrad(1:ngrid,1:nlayer,iaer) = 0.02 ! haze
     126             endif
     127       enddo
     128
     129   end subroutine haze_reffrad_fix
    153130!==================================================================
    154131
    155132
    156 
    157 !==================================================================
    158    subroutine dust_reffrad(ngrid,nlayer,reffrad)
    159 !==================================================================
    160 !     Purpose
    161 !     -------
    162 !     Compute the effective radii of dust particles
    163 !
    164 !     Authors
    165 !     -------
    166 !     Jeremy Leconte (2012)
    167 !
    168 !==================================================================
    169       Implicit none
    170 
    171       integer,intent(in) :: ngrid
    172       integer,intent(in) :: nlayer
    173 
    174       real, intent(out) :: reffrad(ngrid,nlayer)      !dust particles radii (m)
    175            
    176       reffrad(1:ngrid,1:nlayer) = 2.e-6 ! dust
    177 
    178    end subroutine dust_reffrad
    179 !==================================================================
    180 
    181 
    182 !==================================================================
    183    subroutine h2so4_reffrad(ngrid,nlayer,reffrad)
    184 !==================================================================
    185 !     Purpose
    186 !     -------
    187 !     Compute the effective radii of h2so4 particles
    188 !
    189 !     Authors
    190 !     -------
    191 !     Jeremy Leconte (2012)
    192 !
    193 !==================================================================
    194       Implicit none
    195 
    196       integer,intent(in) :: ngrid
    197       integer,intent(in) :: nlayer
    198 
    199       real, intent(out) :: reffrad(ngrid,nlayer)      !h2so4 particle radii (m)
    200                
    201       reffrad(1:ngrid,1:nlayer) = 1.e-6 ! h2so4
    202 
    203    end subroutine h2so4_reffrad
    204 !==================================================================
    205 
    206 !==================================================================
    207    subroutine back2lay_reffrad(ngrid,reffrad,nlayer,pplev)
    208 !==================================================================
    209 !     Purpose
    210 !     -------
    211 !     Compute the effective radii of particles in a 2-layer model
    212 !
    213 !     Authors
    214 !     -------
    215 !     Sandrine Guerlet (2013)
    216 !
    217 !==================================================================
    218       use callkeys_mod, only: pres_bottom_tropo,pres_top_tropo,size_tropo,  &
    219                               pres_bottom_strato,size_strato
    220  
    221       Implicit none
    222 
    223       integer,intent(in) :: ngrid
    224 
    225       real, intent(out) :: reffrad(ngrid,nlayer)      ! particle radii (m)
    226       REAL,INTENT(IN) :: pplev(ngrid,nlayer+1) ! inter-layer pressure (Pa)
    227       INTEGER,INTENT(IN) :: nlayer ! number of atmospheric layers
    228       REAL :: expfactor
    229       INTEGER l,ig
    230            
    231       reffrad(:,:)=1e-6  !!initialization, not important
    232           DO ig=1,ngrid
    233             DO l=1,nlayer-1
    234               IF (pplev(ig,l) .le. pres_bottom_tropo .and. pplev(ig,l) .ge. pres_top_tropo) THEN
    235                 reffrad(ig,l) = size_tropo
    236               ELSEIF (pplev(ig,l) .lt. pres_top_tropo .and. pplev(ig,l) .gt. pres_bottom_strato) THEN
    237                 expfactor=log(size_strato/size_tropo) / log(pres_bottom_strato/pres_top_tropo)
    238                 reffrad(ig,l)= size_tropo*((pplev(ig,l)/pres_top_tropo)**expfactor)
    239               ELSEIF (pplev(ig,l) .le. pres_bottom_strato) then
    240                 reffrad(ig,l) = size_strato
    241               ENDIF
    242             ENDDO
    243           ENDDO
    244 
    245    end subroutine back2lay_reffrad
    246 !==================================================================
    247 
    248133end module radii_mod
    249134!==================================================================
Note: See TracChangeset for help on using the changeset viewer.