Changeset 1822


Ignore:
Timestamp:
Nov 20, 2017, 3:19:07 PM (7 years ago)
Author:
jvatant
Message:

Preliminary modifs for the optical coupling of haze
+ Moved inits of setspi/v before init of mufi
+ Added access to tarcers in optci/v
+ Some coherence in call to directories
JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/callcorrk.F90

    r1788 r1822  
    66          fluxabs_sw,fluxtop_dn,                               &
    77          OLR_nu,OSR_nu,                                       &
    8           firstcall,lastcall)
     8          lastcall)
    99
    1010      use mod_phys_lmdz_para, only : is_master
    1111      use radinc_h
    1212      use radcommon_h
    13       use datafile_mod, only: datadir
    14       use ioipsl_getin_p_mod, only: getin_p
    1513      use gases_h
    1614      USE tracer_h
     15      use callkeys_mod, only: global1d, szangle
    1716      use comcstfi_mod, only: pi, mugaz, cpp
    1817      use callkeys_mod, only: diurnal,tracer,        &
     
    5857      REAL,INTENT(IN) :: fract(ngrid)              ! Fraction of day.
    5958      REAL,INTENT(IN) :: dist_star                 ! Distance star-planet (AU).
    60       logical,intent(in) :: firstcall              ! Signals first call to physics.
    6159      logical,intent(in) :: lastcall               ! Signals last call to physics.
    6260     
     
    107105      INTEGER ig,l,k,nw
    108106
    109       real szangle
    110       logical global1d
    111       save szangle,global1d
    112 !$OMP THREADPRIVATE(szangle,global1d)
    113107      real*8 taugsurf(L_NSPECTV,L_NGAUSS-1)
    114108      real*8 taugsurfi(L_NSPECTI,L_NGAUSS-1)
    115 
    116 
    117       ! Miscellaneous :
    118       character(len=10) :: tmp1
    119       character(len=10) :: tmp2
    120109
    121110      logical OLRz
     
    127116
    128117
    129 !===============================================================
    130 !           I.a Initialization on first call
    131 !===============================================================
    132 
    133 
    134       if(firstcall) then
    135 
    136          call system('rm -f surf_vals_long.out')
    137 
    138 !--------------------------------------------------
    139 !             Set up correlated k
    140 !--------------------------------------------------
    141 
    142 
    143          print*, "callcorrk: Correlated-k data base folder:",trim(datadir)
    144          call getin_p("corrkdir",corrkdir)
    145          print*, "corrkdir = ",corrkdir
    146          write( tmp1, '(i3)' ) L_NSPECTI
    147          write( tmp2, '(i3)' ) L_NSPECTV
    148          banddir=trim(adjustl(tmp1))//'x'//trim(adjustl(tmp2))
    149          banddir=trim(adjustl(corrkdir))//'/'//trim(adjustl(banddir))
    150 
    151          call setspi            ! Basic infrared properties.
    152          call setspv            ! Basic visible properties.
    153          call sugas_corrk       ! Set up gaseous absorption properties.
    154 
    155          OLR_nu(:,:) = 0.
    156          OSR_nu(:,:) = 0.
    157 
    158          if (ngrid.eq.1) then
    159             PRINT*, 'Simulate global averaged conditions ?'
    160             global1d = .false. ! default value
    161             call getin_p("global1d",global1d)
    162             write(*,*) "global1d = ",global1d
    163            
    164             ! Test of incompatibility : if global1d is true, there should not be any diurnal cycle.
    165             if (global1d.and.diurnal) then
    166                print*,'if global1d is true, diurnal must be set to false'
    167                stop
    168             endif
    169 
    170             if (global1d) then
    171                PRINT *,'Solar Zenith angle (deg.) ?'
    172                PRINT *,'(assumed for averaged solar flux S/4)'
    173                szangle=60.0  ! default value
    174                call getin_p("szangle",szangle)
    175                write(*,*) "szangle = ",szangle
    176             endif
    177          endif
    178 
    179       end if ! of if (firstcall)
    180 
    181 !=======================================================================
    182 !          I.b  Initialization on every call   
     118!=======================================================================
     119!             I.  Initialization on every call   
    183120!=======================================================================
    184121 
     
    361298            endif
    362299           
    363             call optcv(dtauv,tauv,taucumv,plevrad,                 &
    364                  wbarv,cosbv,tauray,tmid,pmid,taugsurf)
     300            call optcv(pq,plevrad,tmid,pmid,                       &
     301                 dtauv,tauv,taucumv,wbarv,cosbv,tauray,taugsurf)
    365302
    366303            call sfluxv(dtauv,tauv,taucumv,albv,dwnv,wbarv,cosbv,  &
     
    403340!-----------------------------------------------------------------------
    404341
    405          call optci(plevrad,tlevrad,dtaui,taucumi,                  &
    406               cosbi,wbari,tmid,pmid,taugsurfi)
     342         call optci(pq,plevrad,tlevrad,tmid,pmid,                   &
     343              dtaui,taucumi,cosbi,wbari,taugsurfi)
    407344
    408345         call sfluxi(plevrad,tlevrad,dtaui,taucumi,ubari,albi,      &
  • trunk/LMDZ.TITAN/libf/phytitan/callkeys_mod.F90

    r1795 r1822  
    1414      logical,save :: strictboundcorrk                                     
    1515!$OMP THREADPRIVATE(strictboundcorrk)
    16 
    1716      logical,save :: callchim, callmufi, callclouds
    1817!$OMP THREADPRIVATE(callchim,callmufi,callclouds)
    19 
     18      logical,save :: global1d
     19!$OMP THREADPRIVATE(global1d)
    2020      logical,save :: enertest
    2121      logical,save :: nonideal
     
    4040      integer,save :: ichim
    4141!$OMP THREADPRIVATE(ichim)
    42 
    4342      integer,save :: iddist
    4443      integer,save :: iradia
     
    5150!$OMP THREADPRIVATE(df_mufi, rm_mufi, rho_aer_mufi,p_prod,tx_prod,rc_prod,air_rad)
    5251
     52      real,save :: szangle
     53!$OMP THREADPRIVATE(szangle)
    5354      real,save :: Fat1AU
    5455      real,save :: stelTbb
  • trunk/LMDZ.TITAN/libf/phytitan/datafile_mod.F90

    r1795 r1822  
    1414      character(len=12),parameter :: surfdir="surface_data"
    1515     
     16      ! Default directories for correlated-k data
     17      ! Set in inifis_mod
     18      character(LEN=100),save :: corrkdir = 'datagcm/corrk_data/50X50'
     19      character(LEN=100),save :: banddir  = 'datagcm/corrk_data/50X50/50x50'
     20!$OMP THREADPRIVATE(corrkdir,banddir)
     21     
    1622      ! Default directory for microphysics
    17       character(LEN=300),save :: config_mufi ='datagcm/microphysics/config.cfg'
     23      ! Set in inifis_mod
     24      character(LEN=100),save :: config_mufi ='datagcm/microphysics/config.cfg'
     25!$OMP THREADPRIVATE(config_mufi)
    1826
    1927      end module datafile_mod
  • trunk/LMDZ.TITAN/libf/phytitan/inifis_mod.F90

    r1795 r1822  
    1010
    1111  use radinc_h, only: ini_radinc_h
    12   use datafile_mod, only: datadir,config_mufi
     12  use datafile_mod
    1313  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
    1414  use comgeomfi_h, only: totarea, totarea_planet
     
    220220     call getin_p("corrk",corrk)
    221221     write(*,*) " corrk = ",corrk
     222     
     223     if (corrk) then
     224       ! default path is set in datadir
     225       write(*,*) "callcorrk: Correlated-k data base folder:",trim(datadir)
     226       call getin_p("corrkdir",corrkdir)
     227       write(*,*) " corrkdir = ",corrkdir
     228     endif
     229     
     230     if (corrk .and. ngrid.eq.1) then
     231       write(*,*) "simulate global averaged conditions ?"
     232       global1d = .false. ! default value
     233       call getin_p("global1d",global1d)
     234       write(*,*) " global1d = ",global1d
     235       
     236       ! Test of incompatibility : if global1d is true, there should not be any diurnal cycle.
     237       if (global1d.and.diurnal) then
     238          write(*,*) "if global1d is true, diurnal must be set to false"
     239          stop
     240       endif
     241
     242       if (global1d) then
     243          write(*,*) "Solar Zenith angle (deg.) ?"
     244          write(*,*) "(assumed for averaged solar flux S/4)"
     245          szangle=60.0  ! default value
     246          call getin_p("szangle",szangle)
     247          write(*,*) " szangle = ",szangle
     248       endif
     249     endif
    222250
    223251     write(*,*) "prohibit calculations outside corrk T grid?"
     
    349377     df_mufi=2.0 ! default value
    350378     call getin_p("df_mufi",df_mufi)
     379     write(*,*)" df_mufi = ",df_mufi
    351380
    352381     write(*,*) "Monomer radius (m) ?"
    353382     rm_mufi=6.66e-08 ! default value
    354383     call getin_p("rm_mufi",rm_mufi)
     384     write(*,*)" rm_mufi = ",rm_mufi
    355385
    356386     write(*,*) "Aerosol density (kg.m-3)?"
    357387     rho_aer_mufi=1.e3 ! default value
    358388     call getin_p("rho_aer_mufi",rho_aer_mufi)
     389     write(*,*)" rho_aer_mufi = ",rho_aer_mufi
    359390
    360391     write(*,*) "Pressure level of aer. production (Pa) ?"
    361392     p_prod=1.0 ! default value
    362393     call getin_p("p_prod",p_prod)
     394     write(*,*)" p_prod = ",p_prod
    363395     
    364396     write(*,*) "Aerosol production rate (kg.m-2.s-1) ?"
    365397     tx_prod=3.5e-13 ! default value
    366398     call getin_p("tx_prod",tx_prod)
     399     write(*,*)" tx_prod = ",tx_prod
    367400
    368401     write(*,*) "Equivalent radius production (m) ?"
    369402     rc_prod=2.0e-8 ! default value
    370403     call getin_p("rc_prod",rc_prod)
     404     write(*,*)" rhc_prod = ",rc_prod
    371405
    372406     write(*,*) "Radius of air (nitrogen) molecule (m) ?"
    373407     air_rad=1.75e-10 ! default value
    374408     call getin_p("air_rad",air_rad)
     409     write(*,*)" air_rad = ",air_rad
    375410
    376411     write(*,*) "Path to microphys. config file ?"
    377412     config_mufi='datagcm/microphysics/config.cfg' ! default value
    378413     call getin_p("config_mufi",config_mufi)
     414     write(*,*)" config_mufi = ",config_mufi
    379415
    380416! Soil model
  • trunk/LMDZ.TITAN/libf/phytitan/optci.F90

    r1792 r1822  
    1 subroutine optci(PLEV,TLEV,DTAUI,TAUCUMI,      &
    2      COSBI,WBARI,TMID,PMID,TAUGSURF)
     1subroutine optci(PQ,PLEV,TLEV,TMID,PMID,      &
     2     DTAUI,TAUCUMI,COSBI,WBARI,TAUGSURF)
    33
    44  use radinc_h
     
    1717  !     and COSBAR. For each level it calculates TAU.
    1818  !     
    19   !     TAUI(L,LW) is the cumulative optical depth at level L (or alternatively
     19  !     TAUCUMI(L,LW) is the cumulative optical depth at level L (or alternatively
    2020  !     at the *bottom* of layer L), LW is the spectral wavelength interval.
    2121  !     
     
    2626  !     -------
    2727  !     Adapted from the NASA Ames code by R. Wordsworth (2009)
     28  !     Clean and adaptation to Titan by J. Vatant d'Ollone (2016-17)
    2829  !     
    2930  !==================================================================
    3031
    3132
    32   real*8 DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     33  !==========================================================
     34  ! Input/Output
     35  !==========================================================
     36  REAL*8, INTENT(IN)  :: PQ ! Tracers (kg/kg_of_air).
     37  REAL*8, INTENT(IN)  :: PLEV(L_LEVELS), TLEV(L_LEVELS)
     38  REAL*8, INTENT(IN)  :: TMID(L_LEVELS), PMID(L_LEVELS)
     39 
     40  REAL*8, INTENT(OUT) :: DTAUI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     41  REAL*8, INTENT(OUT) :: TAUCUMI(L_LEVELS,L_NSPECTI,L_NGAUSS)
     42  REAL*8, INTENT(OUT) :: COSBI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     43  REAL*8, INTENT(OUT) :: WBARI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
     44  REAL*8, INTENT(OUT) :: TAUGSURF(L_NSPECTI,L_NGAUSS-1)
     45  ! ==========================================================
     46 
    3347  real*8 DTAUKI(L_LEVELS,L_NSPECTI,L_NGAUSS)
    34   real*8 TAUI(L_NLEVRAD,L_NSPECTI,L_NGAUSS)
    35   real*8 TAUCUMI(L_LEVELS,L_NSPECTI,L_NGAUSS)
    36   real*8 PLEV(L_LEVELS)
    37   real*8 TLEV(L_LEVELS)
    38   real*8 TMID(L_LEVELS), PMID(L_LEVELS)
    39   real*8 COSBI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
    40   real*8 WBARI(L_NLAYRAD,L_NSPECTI,L_NGAUSS)
    4148
    4249  ! Titan customisation
     
    5865  real*8  LCOEF(4), LKCOEF(L_LEVELS,4)
    5966
    60   real*8 taugsurf(L_NSPECTI,L_NGAUSS-1)
    6167  real*8 DCONT
    6268  double precision wn_cont, p_cont, p_air, T_cont, dtemp, dtempc
  • trunk/LMDZ.TITAN/libf/phytitan/optcv.F90

    r1792 r1822  
    1 SUBROUTINE OPTCV(DTAUV,TAUV,TAUCUMV,PLEV,  &
    2      WBARV,COSBV,TAURAY,TMID,PMID,TAUGSURF)
     1SUBROUTINE OPTCV(PQ,PLEV,TMID,PMID,  &
     2     DTAUV,TAUV,TAUCUMV,WBARV,COSBV,TAURAY,TAUGSURF)
    33
    44  use radinc_h
     
    1919  !     -------
    2020  !     Adapted from the NASA Ames code by R. Wordsworth (2009)
     21  !     Clean and adaptation to Titan by J. Vatant d'Ollone (2016-17)
    2122  !     
    2223  !==================================================================
     
    3738
    3839
    39   real*8 DTAUV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     40  !==========================================================
     41  ! Input/Output
     42  !==========================================================
     43  REAL*8, INTENT(IN)  :: PQ ! Tracers (kg/kg_of_air).
     44  REAL*8, INTENT(IN)  :: PLEV(L_LEVELS)
     45  REAL*8, INTENT(IN)  :: TMID(L_LEVELS), PMID(L_LEVELS)
     46 
     47  REAL*8, INTENT(OUT) :: DTAUV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     48  REAL*8, INTENT(OUT) :: TAUV(L_NLEVRAD,L_NSPECTV,L_NGAUSS)
     49  REAL*8, INTENT(OUT) :: TAUCUMV(L_LEVELS,L_NSPECTV,L_NGAUSS)
     50  REAL*8, INTENT(OUT) :: COSBV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     51  REAL*8, INTENT(OUT) :: WBARV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
     52  ! ==========================================================
     53 
    4054  real*8 DTAUKV(L_LEVELS,L_NSPECTV,L_NGAUSS)
    41   real*8 TAUV(L_NLEVRAD,L_NSPECTV,L_NGAUSS)
    42   real*8 TAUCUMV(L_LEVELS,L_NSPECTV,L_NGAUSS)
    43   real*8 PLEV(L_LEVELS)
    44   real*8 TMID(L_LEVELS), PMID(L_LEVELS)
    45   real*8 COSBV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    46   real*8 WBARV(L_NLAYRAD,L_NSPECTV,L_NGAUSS)
    4755
    4856  ! Titan customisation
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1812 r1822  
    2020      use comsaison_h, only: mu0, fract, dist_star, declin, right_ascen
    2121      use comsoil_h, only: nsoilmx, layer, mlayer, inertiedat
     22      use datafile_mod, only: datadir, corrkdir, banddir
    2223      use geometry_mod, only: latitude, longitude, cell_area
    2324      USE comgeomfi_h, only: totarea, totarea_planet
     
    3738      use callkeys_mod
    3839      use vertical_layers_mod, only: presnivs, pseudoalt
     40      use ioipsl_getin_p_mod, only: getin_p
    3941#ifdef CPP_XIOS     
    4042      use xios_output_mod, only: initialize_xios_output, &
     
    308310
    309311
     312
    310313! local variables for DIAGNOSTICS : (diagfi & stat)
    311314! -------------------------------------------------
     
    349352      real,allocatable,dimension(:,:),save :: qsurf_hist
    350353!$OMP THREADPRIVATE(qsurf_hist)
     354   
     355      ! Miscellaneous :
     356      character(len=10) :: tmp1
     357      character(len=10) :: tmp2
    351358
    352359! Local variables for Titan chemistry and microphysics (JVO 2017)
     
    458465         zdtlw(:,:) = 0.0
    459466
     467!        Initialize setup for correlated-k radiative transfer
     468!        JVO 17 : Was in callcorrk firstcall, but we need spectral intervals for microphysics
     469!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     470
     471         if (corrk) then
     472         
     473           call system('rm -f surf_vals_long.out')
     474
     475           write( tmp1, '(i3)' ) L_NSPECTI
     476           write( tmp2, '(i3)' ) L_NSPECTV
     477           banddir=trim(adjustl(tmp1))//'x'//trim(adjustl(tmp2))
     478           banddir=trim(adjustl(corrkdir))//'/'//trim(adjustl(banddir))
     479
     480           call setspi            ! Basic infrared properties.
     481           call setspv            ! Basic visible properties.
     482           call sugas_corrk       ! Set up gaseous absorption properties.
     483         
     484           OLR_nu(:,:) = 0.
     485           OSR_nu(:,:) = 0.
     486           
     487         endif
     488
    460489!        Initialize names, timestep and saturation profiles for chemistry
    461490!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     
    517546           stop
    518547         endif
    519 
    520548         write (*,*) 'In physiq day_ini =', day_ini
    521549
     
    792820                              fluxsurfabs_sw,fluxtop_lw,                          &
    793821                              fluxabs_sw,fluxtop_dn,OLR_nu,OSR_nu,                &
    794                               firstcall,lastcall)
     822                              lastcall)
    795823
    796824               ! Radiative flux from the sky absorbed by the surface (W.m-2).
  • trunk/LMDZ.TITAN/libf/phytitan/radinc_h.F90

    r1788 r1822  
    7979      !real*8,parameter :: NTfac = 1.0D+2   
    8080
    81       character(len=100),save :: corrkdir
    82 !$OMP THREADPRIVATE(corrkdir)
    83 
    84       character(len=100),save :: banddir
    85 !$OMP THREADPRIVATE(banddir)
    86 
    8781contains
    8882
  • trunk/LMDZ.TITAN/libf/phytitan/setspi.F90

    r1788 r1822  
    2222!==================================================================
    2323
    24       use radinc_h,    only: L_NSPECTI,corrkdir,banddir,NTstar,NTstop,NTfac
     24      use radinc_h,    only: L_NSPECTI,NTstar,NTstop,NTfac
    2525      use radcommon_h, only: BWNI,WNOI,DWNI,WAVEI,planckir,sigma
    26       use datafile_mod, only: datadir
     26      use datafile_mod, only: datadir, corrkdir, banddir
    2727      use comcstfi_mod, only: pi
    2828
  • trunk/LMDZ.TITAN/libf/phytitan/setspv.F90

    r1788 r1822  
    2323!==================================================================
    2424
    25       use radinc_h,    only: L_NSPECTV, corrkdir, banddir
     25      use radinc_h,    only: L_NSPECTV
    2626      use radcommon_h, only: BWNV,WNOV,DWNV,WAVEV, &
    2727                             STELLARF,TAURAY
    28       use datafile_mod, only: datadir
     28      use datafile_mod, only: datadir, corrkdir, banddir
    2929      use callkeys_mod, only: Fat1AU,rayleigh
    3030
  • trunk/LMDZ.TITAN/libf/phytitan/sugas_corrk.F90

    r1648 r1822  
    2525      use radcommon_h, only : gasv,gasi,FZEROI,FZEROV,gweight
    2626      use radcommon_h, only : WNOI,WNOV
    27       use datafile_mod, only: datadir
     27      use datafile_mod, only: datadir, corrkdir, banddir
    2828      use comcstfi_mod, only: mugaz
    2929      use gases_h
Note: See TracChangeset for help on using the changeset viewer.