Ignore:
Timestamp:
Jan 19, 2017, 2:46:53 PM (8 years ago)
Author:
jvatant
Message:

Modifications to custom radiative transfer to Titan
+ Enables an altitude dependant gfrac for CIA computations

-> many radical changes in su_gases and co ..
-> read vertical CH4 profile with call_profilgases
-> Now you need a 'profile.def' that I will add in the deftank

+ Added interpolate CIA routines for CH4
+ Added temporary mean aerosol profile opacity routine (disr_haze)

File:
1 edited

Legend:

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

    r1647 r1648  
    2424      use radcommon_h, only : tgasref,tgasmin,tgasmax
    2525      use radcommon_h, only : gasv,gasi,FZEROI,FZEROV,gweight
    26       use radcommon_h, only : wrefvar,WNOI,WNOV
     26      use radcommon_h, only : WNOI,WNOV
    2727      use datafile_mod, only: datadir
    2828      use comcstfi_mod, only: mugaz
     
    4444      ! ALLOCATABLE ARRAYS -- AS 12/2011
    4545      REAL*8, DIMENSION(:,:,:,:,:), ALLOCATABLE,SAVE :: gasi8, gasv8    !read by master
    46       character*20,allocatable,DIMENSION(:),SAVE :: gastype ! for check with gnom, read by master
    4746
    4847      real*8 x, xi(4), yi(4), ans, p
     
    7978      read(111,*) ngas
    8079
    81       if(ngas.ne.ngasmx)then
    82          print*,'Number of gases in radiative transfer data (',ngas,') does not', &
    83                 'match that in gases.def (',ngasmx,'), exiting.'
    84          call abort
    85       endif
    86 
    8780      if(ngas.gt.5 .or. ngas.lt.1)then
    8881         print*,ngas,' species in database [',               &
     
    9083                '], radiative code cannot handle this.'
    9184         call abort
    92       endif
    93 
    94       ! dynamically allocate gastype and read from Q.dat
    95       IF ( .NOT. ALLOCATED( gastype ) ) ALLOCATE( gastype( ngas ) )
    96 
    97       do igas=1,ngas
    98          read(111,*) gastype(igas)
    99          print*,'Gas ',igas,' is ',gastype(igas)
    100       enddo
    101 
    102       ! get array size, load the coefficients
    103       open(111,file=TRIM(file_path),form='formatted')
    104       read(111,*) L_REFVAR
    105       IF( .NOT. ALLOCATED( wrefvar ) ) ALLOCATE( WREFVAR(L_REFVAR) )
    106       read(111,*) wrefvar
    107       close(111)
    108 
    109       ! Check that gastype and gnom match
    110       do igas=1,ngas
    111          print*,'Gas ',igas,' is ',trim(gnom(igas))
    112          if (trim(gnom(igas)).ne.trim(gastype(igas))) then
    113             print*,'Name of a gas in radiative transfer data (',trim(gastype(igas)),') does not ', &
    114                  'match that in gases.def (',trim(gnom(igas)),'), exiting. You should compare ', &
    115                  'gases.def with Q.dat in your radiative transfer directory.'
    116             call abort
    117          endif
    118       enddo
    119       print*,'Confirmed gas match in radiative transfer and gases.def!'
    120 
    121       ! display the values
    122       print*,'Variable gas volume mixing ratios:'
    123       do n=1,L_REFVAR
    124          !print*,n,'.',wrefvar(n),' kg/kg' ! pay attention!
    125          print*,n,'.',wrefvar(n),' mol/mol'
    126       end do
    127       print*,''
     85      endif
     86     
     87      L_REFVAR = 1 ! JVO 2017 : set to 1 to keep the code running until the new variable species treatment
    12888
    12989!=======================================================================
     
    628588            enddo
    629589
    630          endif
    631 
     590         elseif (igas .eq. igas_CH4) then
     591
     592            ! first do self-induced absorption
     593            dummy = -9999
     594            call interpolateCH4CH4(200.D+0,200.D+0,7500.D+0,testcont,.true.,dummy)
     595            ! then cross-interactions with other gases
     596            do jgas=1,ngasmx
     597               if (jgas .eq. igas_N2) then
     598                  dummy = -9999
     599                  call interpolateN2CH4(200.D+0,250.0D+0,100000.D+0,5000.D+0,testcont,.true.,dummy)
     600               endif
     601            enddo
     602
     603         endif 
     604         
    632605      enddo
    633606      endif
     
    645618      IF( ALLOCATED( gasv8 ) ) DEALLOCATE( gasv8 )
    646619      IF( ALLOCATED( pgasref ) ) DEALLOCATE( pgasref )
    647       IF( ALLOCATED( gastype ) ) DEALLOCATE( gastype )
    648620!$OMP END MASTER
    649621!$OMP BARRIER
Note: See TracChangeset for help on using the changeset viewer.