Ignore:
Timestamp:
Jun 4, 2015, 4:23:32 PM (10 years ago)
Author:
slebonnois
Message:

SL: update of the Venus GCM, + corrections on routines used for newstart/start2archive for Titan and Venus, + some modifications on tools

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/nirco2abs.F

    r1310 r1442  
    11      SUBROUTINE nirco2abs(nlon,nlev,nplay,dist_sol,nq,pq,
    2      $     mu0,fract,pdtnirco2,
    3      $     co2vmr_gcm, ovmr_gcm)
     2     $     mu0,fract,pdtnirco2)
    43
    54       use dimphy
    65       use comgeomphy, only: rlatd, rlond     
     6       use chemparam_mod, only: i_co2, i_o
    77c       use compo_hedin83_mod2
    88
     
    2323c   Stephen Lewis 2000
    2424c
    25 C   jan 2014 g.gilli     
     25c   oct 2014 g.gilli     Coupling with photochemical model
     26C   jan 2014 g.gilli     Revision (following martian non-lte param)   
    2627C   jun 2013 l.salmi     First adaptation to Venus and NIR NLTE param
    2728c   jul 2011 malv+fgg    New corrections for NLTE implemented
     
    5960#include "nirdata.h"
    6061c#include "tracer.h"
    61 
     62#include "mmol.h"
    6263c-----------------------------------------------------------------------
    6364c    Input/Output
    6465c    ------------
    6566      integer,intent(in) :: nlon ! number of (horizontal) grid points
    66      
    6767      integer,intent(in) :: nlev ! number of atmospheric layers
     68
    6869      real,intent(in) :: nplay(nlon,nlev) ! Pressure
    6970      real,intent(in) :: dist_sol ! Sun-Venus distance (in AU)
    7071      integer,intent(in) :: nq ! number of tracers
    71       real,intent(in) :: pq(nlon,nlev,nq) ! tracers
     72      real,intent(in) :: pq(nlon,nlev,nq) ! mass mixing ratio tracers
    7273      real,intent(in) :: mu0(nlon) ! solar angle
    7374      real,intent(in) :: fract(nlon) ! day fraction of the time interval
    7475c      real,intent(in) :: declin ! latitude of sub-solar point
    75 
    76       real co2vmr_gcm(nlon,nlev),ovmr_gcm(nlon,nlev)
    77 
     76      real :: co2vmr_gcm(nlon,nlev), o3pvmr_gcm(nlon,nlev)
     77 
    7878      real,intent(out) :: pdtnirco2(nlon,nlev) ! heating rate (K/sec)
    7979
     
    9595      integer,save :: io=0 ! index of "o" tracer
    9696
    97 ccc
     97cccc     parameters for CO2 heating fit
    9898c
    9999c     n_a  =  heating rate for Venusian day at p0, r0, mu =0 [K day-1]
     
    104104      real n_a, n_p0, n_b, p_ctop
    105105
    106 cc Current values
    107        parameter (n_a = 18.13/86400.0)    !!     K/Eday  ---> K/sec   
     106   
     107cc "Nominal" values
     108       parameter (n_a = 18.13/86400.0)     !c     K/Eday  ---> K/sec   
    108109       parameter (p_ctop=13.2e2)
     110c    -- NLTE Param v3  --
     111       parameter (n_p0=0.008) 
     112       parameter (n_b=1.362)
     113
     114cc   -- Varoxy5
     115C       parameter (n_a = 20/86400.0)
     116C       parameter (p_ctop=870)   ! [Pa]
     117C       parameter (n_b=1.98)
     118C       parameter (n_p0=0.045)
     119
     120c      parameter (n_p0=0.1) !!!!cccc test varoxy5mod
     121c      parameter (n_b=0.9)
     122
    109123
    110124c    -- NLTE Param v2  --
    111 c       parameter (n_p0=0.01) 
     125C       parameter (n_p0=0.01) 
    112126c       parameter (n_b = 1.3)
    113  
    114 ccc TESTS 
    115 c       parameter (n_a = 18.4/86400.0 *0.6) 
    116 c       parameter (p_ctop=63.9e2)
    117 c       parameter (n_p0=0.012)
    118 c       parameter (n_b=1.9628251)
    119 
    120 
    121 c    -- NLTE Param v1  --
    122 c       parameter (n_p0=0.012)   
    123 c       parameter (n_b = 1.4)
    124 
    125 c    -- NLTE Param v3  --
    126 
    127        parameter (n_p0=0.008)   
    128        parameter (n_b = 1.362)
     127   
    129128
    130129
     
    134133      real    p2011,cociente1,merge
    135134      real    cor0,oco2gcm
    136 
    137 c     co2heat is the heating by CO2 at p_ctop=9.3E03 Pa (cloud top 65 km) for a zero zenithal angle.
     135!!!!
     136c      real :: pic27(nlon,nlev), pic27b(nlon,nlev)
     137c      real :: pic43(nlon,nlev), picnir(nlon,nlev)
     138
     139c     co2heat is the heating by CO2 at p_ctop=13.2e2 for a zero zenithal angle.
    138140
    139141      co2heat0=n_a*(0.72/dist_sol)**2     
    140142
    141 
    142 CCCCCC   TEST: reduce/incrise by 50% nir Heating
    143 
    144 c      co2heat0  = co2heat0 * 2
     143CCCCCC   TEST: reduce by X% nir Heating
     144
     145c      co2heat0  = co2heat0 * 0.8
    145146
    146147
     
    149150c     Initialisation
    150151c     --------------
    151 c      if (firstcall) then
    152 c        if (nircorr.eq.1) then
    153 cc          ! we will need co2 and o tracers
    154 c          ico2= igcm_co2
    155 c          if (ico2==0) then
    156 c            write(*,*) "nirco2abs error: I need a CO2 tracer"
    157 c            write(*,*) "     when running with nircorr==1"
    158 c           stop
    159 c          endif
    160 c          io=igcm_o
    161 c          if (io==0) then
    162 c            write(*,*) "nirco2abs error: I need an O tracer"
    163 c            write(*,*) "     when running with nircorr==1"
    164 c            stop
    165 c          endif
    166 c        endif
    167 c        firstcall=.false.
    168 c      endif
     152      if (firstcall) then
     153        if (nircorr.eq.1) then
     154c          ! we will need co2 and o tracers
     155          ico2= i_co2
     156          if (ico2==0) then
     157            write(*,*) "nirco2abs error: I need a CO2 tracer"
     158            write(*,*) "     when running with nircorr==1"
     159           stop
     160          endif
     161          io=i_o
     162          if (io==0) then
     163            write(*,*) "nirco2abs error: I need an O tracer"
     164            write(*,*) "     when running with nircorr==1"
     165            stop
     166          endif
     167        endif
     168        firstcall=.false.
     169      endif
    169170
    170171     
     
    178179            zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35.
    179180
    180             
     181           
    181182            if(nircorr.eq.1) then
    182183               do l=1,nlev
     
    187188               call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
    188189               call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
    189 
     190               
    190191            endif
    191192
    192193            do l=1,nlev
     194     
    193195c           Calculations for the O/CO2 correction
    194196               if(nircorr.eq.1) then
    195197                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
    196                   if(co2vmr_gcm(ig,l).gt.1.e-6) then
    197                      oco2gcm=ovmr_gcm(ig,l)/co2vmr_gcm(ig,l)
     198                  if(pq(ig,l,ico2) .gt. 1.e-6) then
     199                     oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
     200
    198201                  else
    199202                     oco2gcm=1.e6
    200203                  endif
    201204                  cociente1=oco2gcm/oldoco2(l)
     205                 
     206c                  WRITE(*,*) "nirco2abs line 211", l, cociente1
     207
    202208                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
    203209     $                 (1.-alfa2(l))
     
    209215                  cor1(l)=1.
    210216               endif
    211 
    212217
    213218              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
     
    216221c           Corrections from tabulation
    217222     $              * cor1(l) * p2011
    218 
    219 
     223             
    220224          enddo
    221225         enddo
     
    250254
    251255               do l=1,nlev
    252                   if(nircorr.eq.1) then
    253                       cor0=1./(1.+n_p0/nplay(ig,l))**n_b
    254 c                     oco2gcm=ovmr_gcm(ig,l)/co2vmr_gcm(ig,l)
    255                      cociente1 = 1
    256                      merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
    257      $                    (1.-alfa2(l))
    258                      merge=10**merge
    259                      p2011=sqrt(merge)*cor0
    260                   else if (nircorr.eq.0) then
    261                      p2011=1.
    262                      cor1(l)=1.
    263                   endif
    264 
    265 c
    266 
    267                   if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
    268      &                 pdtnirco2(ig,l) + (1/float(nstep))*
    269      &                 co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
    270      &                 /(1.+n_p0/nplay(ig,l))**n_b
    271 !                      Corrections from tabulation
    272      $                 * cor1(l) * p2011
     256c           Calculations for the O/CO2 correction
     257               if(nircorr.eq.1) then
     258                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
     259                  oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
     260                  cociente1=oco2gcm/oldoco2(l)
     261                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
     262     $                 (1.-alfa2(l))
     263                  merge=10**merge
     264                  p2011=sqrt(merge)*cor0
     265
     266               else if (nircorr.eq.0) then
     267                  p2011=1.
     268                  cor1(l)=1.
     269               endif
     270
     271               if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
     272     &              pdtnirco2(ig,l) + (1/float(nstep))*
     273     &              co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
     274     &              /(1.+n_p0/nplay(ig,l))**n_b
     275!     Corrections from tabulation
     276     $              * cor1(l) * p2011
    273277
    274278               enddo
     
    276280         end do
    277281     
    278       END IF
     282
     283      END IF 
    279284
    280285      return
    281286      end
    282 
    283287
    284288     
     
    294298      do n1=1,nlev
    295299         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
    296             escout(n1) = 0.0
     300c            escout(n1) = 0.0
     301            escout(n1) = 1.e-15
    297302         else
    298303            do n = 1,nl-1
Note: See TracChangeset for help on using the changeset viewer.