Changeset 2283 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Apr 9, 2020, 6:34:53 PM (5 years ago)
Author:
jvatant
Message:

Set the temperature boundaries and step for Planck function integration as input in callphys.def, for more flexibility.

+ User can now set them by tplanckmin, tplanckmax and dtplanck
+ Default values are a wide range 30-1500K
+ Add a sanity check in callcorrk instead of leaving out-of-bounds planckir indexes.

--JVO

Location:
trunk/LMDZ.GENERIC
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r2278 r2283  
    15251525- Get rid of "zerophys"; modern Fortran syntax is better to initialize an
    15261526  array.
     1527
     1528== 09/04/2020 (r2283) == JVO
     1529+ Set the temperature boundaries and step for Planck function
     1530  integration as input in callphys.def, for more flexibility.
     1531  + User can now set them by tplanckmin, tplanckmax and dtplanck
     1532  + Default values are a wide range 30-1500K
     1533  + Add a sanity check in callcorrk instead of leaving out-of-bounds planckir indexes.
     1534
     1535
  • trunk/LMDZ.GENERIC/libf/phystd/callcorrk.F90

    r2269 r2283  
    3232      use comcstfi_mod, only: pi, mugaz, cpp
    3333      use callkeys_mod, only: varactive,diurnal,tracer,water,varfixed,satval,diagdtau,    &
    34                               kastprof,strictboundcorrk,specOLR,CLFvarying
     34                              kastprof,strictboundcorrk,specOLR,CLFvarying,               &
     35                              tplanckmin,tplanckmax
    3536      use optcv_mod, only: optcv
    3637      use optci_mod, only: optci
     
    739740
    740741      ! Test for out-of-bounds temperature.
     742      ! -- JVO 20 : Also add a sanity test checking that tlevrad is
     743      !             within Planck function temperature boundaries,
     744      !             which would cause gfluxi/sfluxi to crash.
    741745      do k=1,L_LEVELS
     746
    742747         if(tlevrad(k).lt.tgasmin)then
    743748            print*,'Minimum temperature is outside the radiative'
     
    773778            endif
    774779         endif
     780
     781         if (tlevrad(k).lt.tplanckmin) then
     782            print*,'Minimum temperature is outside the boundaries for'
     783            print*,'Planck function integration set in callphys.def, aborting.'
     784            print*,"k=",k," tlevrad(k)=",tlevrad(k)
     785            print*,"tplanckmin=",tplanckmin
     786            message="Minimum temperature outside Planck function bounds - Change tplanckmin in callphys.def"
     787            call abort_physic(subname,message,1)
     788          else if (tlevrad(k).gt.tplanckmax) then
     789            print*,'Maximum temperature is outside the boundaries for'
     790            print*,'Planck function integration set in callphys.def, aborting.'
     791            print*,"k=",k," tlevrad(k)=",tlevrad(k)
     792            print*,"tplanckmax=",tplanckmax
     793            message="Maximum temperature outside Planck function bounds - Change tplanckmax in callphys.def"
     794            call abort_physic(subname,message,1)
     795          endif
     796
    775797      enddo
     798
    776799      do k=1,L_NLAYRAD+1
    777800         if(tmid(k).lt.tgasmin)then
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r2245 r2283  
    6969!$OMP THREADPRIVATE(versH2H2cia,iddist,iaervar,iradia,startype)
    7070
     71      real,save :: tplanckmin
     72      real,save :: tplanckmax
     73      real,save :: dtplanck
     74!$OMP THREADPRIVATE(tplanckmin,tplanckmax,dtplanck)
    7175      real,save :: topdustref
    7276      real,save :: Nmix_co2
  • trunk/LMDZ.GENERIC/libf/phystd/gfluxi.F

    r2056 r2283  
    8585         LAMDA(L) = ALPHA(L)*(1.0D0-W0(L)*COSBAR(L))/UBARI
    8686         
    87          NT    = int(TLEV(2*L)*NTfac)   - NTstar+1
    88          NT2   = int(TLEV(2*L+2)*NTfac) - NTstar+1
     87         NT    = int(TLEV(2*L)*NTfac)   - NTstart+1
     88         NT2   = int(TLEV(2*L+2)*NTfac) - NTstart+1
    8989         
    9090! AB : PLANCKIR(NW,NT) is replaced by P1, the linear interpolation result for a temperature NT
     
    112112      ! -- same results for most thin atmospheres
    113113      ! -- and stabilizes integrations
    114       NT    = int(TLEV(2*L+1)*NTfac) - NTstar+1
     114      NT    = int(TLEV(2*L+1)*NTfac) - NTstart+1
    115115      !! For deep, opaque, thick first layers (e.g. Saturn)
    116116      !! what is below works much better, not unstable, ...
    117117      !! ... and actually fully accurate because 1st layer temp (JL)
    118       !NT    = int(TLEV(2*L)*NTfac) - NTstar+1
     118      !NT    = int(TLEV(2*L)*NTfac) - NTstart+1
    119119      !! (or this one yields same results
    120       !NT    = int( (TLEV(2*L)+TLEV(2*L+1))*0.5*NTfac ) - NTstar+1
    121      
    122       NT2   = int(TLEV(2*L)*NTfac)   - NTstar+1
     120      !NT    = int( (TLEV(2*L)+TLEV(2*L+1))*0.5*NTfac ) - NTstart+1
     121     
     122      NT2   = int(TLEV(2*L)*NTfac)   - NTstart+1
    123123     
    124124! AB : PLANCKIR(NW,NT) is replaced by P1, the linear interpolation result for a temperature NT
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r2254 r2283  
    233233     write(*,*) "strictboundcorrk = ",strictboundcorrk
    234234
     235     write(*,*) "Minimum atmospheric temperature for Planck function integration ?"
     236     tplanckmin=30.0 ! default value
     237     call getin_p("tplanckmin",tplanckmin)
     238     write(*,*) " tplanckmin = ",tplanckmin
     239 
     240     write(*,*) "Maximum atmospheric temperature for Planck function integration ?"
     241     tplanckmax=1500.0 ! default value
     242     call getin_p("tplanckmax",tplanckmax)
     243     write(*,*) " tplanckmax = ",tplanckmax
     244 
     245     write(*,*) "Temperature step for Planck function integration ?"
     246     dtplanck=0.1 ! default value
     247     call getin_p("dtplanck",dtplanck)
     248     write(*,*) " dtplanck = ",dtplanck
     249 
    235250     write(*,*) "call gaseous absorption in the visible bands?", &
    236251                    "(matters only if callrad=T)"
     
    809824#endif
    810825  ! initialize variables in radinc_h
    811   call ini_radinc_h(nlayer)
     826  call ini_radinc_h(nlayer,tplanckmin,tplanckmax,dtplanck)
    812827 
    813828  ! allocate "comsoil_h" arrays
  • trunk/LMDZ.GENERIC/libf/phystd/radcommon_h.F90

    r2142 r2283  
    11module radcommon_h
    2       use radinc_h, only: L_NSPECTI, L_NSPECTV, NTstar, NTstop, &
     2      use radinc_h, only: L_NSPECTI, L_NSPECTV, NTstart, NTstop, &
    33                          naerkind, nsizemax
    44      implicit none
     
    123123      REAL,SAVE :: tstellar ! Stellar brightness temperature (SW)
    124124
    125       real*8,save :: planckir(L_NSPECTI,NTstop-NTstar+1)
     125      REAL*8, DIMENSION(:,:), ALLOCATABLE, SAVE :: planckir
    126126
    127127      real*8,save :: PTOP
  • trunk/LMDZ.GENERIC/libf/phystd/radinc_h.F90

    r2026 r2283  
    7272
    7373      ! For Planck function integration:
    74       ! equivalent temperatures are 1/NTfac of these values
    75       integer, parameter :: NTstar = 500
    76       integer, parameter :: NTstop = 15000 ! new default for all non hot Jupiter runs
    77       real*8, parameter :: NTfac = 1.0D+1 
    78       !integer, parameter :: NTstar = 1000
    79       !integer, parameter :: NTstop = 25000
    80       !real*8,parameter :: NTfac = 5.0D+1   
    81       !integer, parameter :: NTstar = 2000
    82       !integer, parameter :: NTstop = 50000
    83       !real*8,parameter :: NTfac = 1.0D+2   
     74      ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     75      ! Integration boundary temperatures are NTstart/NTfac and Ntstop/NTfac
     76      ! -- JVO 20 : Now read boundary T and integration dT as inputs in callphys.def
     77      !             NTstart, Nstop and NTfac then set by ini_radinc_h
     78      !             Smart user can adjust values depending he's running hot or cold atm
     79      !             Default is wide range : 30K-1500K, with 0.1K step
     80      !             ->  NTstart=300, Nstop=15000, NTfac=10
     81      integer :: NTstart, NTstop
     82      real*8  :: NTfac
    8483
    8584      ! Maximum number of grain size classes for aerosol convolution:
     
    9695contains
    9796
    98   subroutine ini_radinc_h(nbp_lev)
     97  subroutine ini_radinc_h(nbp_lev,tplanckmin,tplanckmax,dtplanck)
    9998  ! Initialize module variables
    10099  implicit none
    101100  integer,intent(in) :: nbp_lev
     101  real*8, intent(in) :: tplanckmin
     102  real*8, intent(in) :: tplanckmax
     103  real*8, intent(in) :: dtplanck
    102104 
    103105  L_NLAYRAD = nbp_lev
    104   L_LEVELS = 2*(nbp_lev-1)+3
     106  L_LEVELS  = 2*(nbp_lev-1)+3
    105107  L_NLEVRAD = nbp_lev+1
    106  
     108
     109  NTfac   = 1.D0 / dtplanck
     110  NTstart = int(tplanckmin * NTfac)
     111  NTstop  = int(tplanckmax * NTfac)
     112 
    107113  end subroutine
    108114
  • trunk/LMDZ.GENERIC/libf/phystd/setspi.F90

    r1397 r2283  
    2222!==================================================================
    2323
    24       use radinc_h,    only: L_NSPECTI,corrkdir,banddir,NTstar,NTstop,NTfac
     24      use radinc_h,    only: L_NSPECTI,corrkdir,banddir,NTstart,NTstop,NTfac
    2525      use radcommon_h, only: BWNI,BLAMI,WNOI,DWNI,WAVEI,planckir,sigma
    2626      use datafile_mod, only: datadir
     
    149149      print*,''
    150150      print*,'setspi: Current Planck integration range:'
    151       print*,'T = ',dble(NTstar)/NTfac, ' to ',dble(NTstop)/NTfac,' K.'
     151      print*,'T = ',dble(NTstart)/NTfac, ' to ',dble(NTstop)/NTfac,' K.'
     152
     153      IF(.NOT.ALLOCATED(planckir)) ALLOCATE(planckir(L_NSPECTI,NTstop-NTstart+1))
    152154
    153155      do NW=1,L_NSPECTI
     
    156158         bpa = (b+a)/2.0D0
    157159         bma = (b-a)/2.0D0
    158          do nt=NTstar,NTstop
     160         do nt=NTstart,NTstop
    159161            T   = dble(NT)/NTfac
    160162            ans = 0.0D0
     
    165167            end do
    166168
    167             planckir(NW,nt-NTstar+1) = ans*bma/(PI*DWNI(NW))
     169            planckir(NW,nt-NTstart+1) = ans*bma/(PI*DWNI(NW))
    168170         end do
    169171      end do
     
    172174      if(forceEC)then
    173175         print*,'setspi: Force F=sigma*eps*T^4 for all values of T!'
    174          do nt=NTstar,NTstop
     176         do nt=NTstart,NTstop
    175177            plancksum=0.0D0
    176178            T=dble(NT)/NTfac
     
    178180            do NW=1,L_NSPECTI
    179181               plancksum=plancksum+  &
    180                   planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
     182                  planckir(NW,nt-NTstart+1)*DWNI(NW)*pi
    181183            end do
    182184
    183185            do NW=1,L_NSPECTI
    184                planckir(NW,nt-NTstar+1)=     &
    185                   planckir(NW,nt-NTstar+1)*  &
     186               planckir(NW,nt-NTstart+1)=     &
     187                  planckir(NW,nt-NTstart+1)*  &
    186188                          sigma*(dble(nt)/NTfac)**4/plancksum
    187189            end do
     
    192194         ! check energy conservation at lower temperature boundary
    193195         plancksum=0.0D0
    194          nt=NTstar
     196         nt=NTstart
    195197         do NW=1,L_NSPECTI
    196             plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
     198            plancksum=plancksum+planckir(NW,nt-NTstart+1)*DWNI(NW)*pi
    197199         end do
    198200         print*,'setspi: At lower limit:'
     
    204206         nt=NTstop
    205207         do NW=1,L_NSPECTI
    206             plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
     208            plancksum=plancksum+planckir(NW,nt-NTstart+1)*DWNI(NW)*pi
    207209         end do
    208210         print*,'setspi: At upper limit:'
  • trunk/LMDZ.GENERIC/libf/phystd/sfluxi.F

    r2056 r2283  
    6767      TSURF = TLEV(L_LEVELS)
    6868
    69       NTS   = int(TSURF*NTfac)-NTstar+1
    70       NTT   = int(TTOP *NTfac)-NTstar+1
     69      NTS   = int(TSURF*NTfac)-NTstart+1
     70      NTT   = int(TTOP *NTfac)-NTstart+1
    7171
    7272!JL12 corrects the surface planck function so that its integral is equal to sigma Tsurf^4
Note: See TracChangeset for help on using the changeset viewer.