Changeset 3455 for trunk


Ignore:
Timestamp:
Oct 9, 2024, 2:06:39 PM (6 weeks ago)
Author:
afalco
Message:

Pluto PCM: added conduction & molvis.
AF

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
6 added
5 edited

Legend:

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

    r3372 r3455  
    66      logical,save :: calladj,calltherm,n2cond,callsoil
    77!$OMP THREADPRIVATE(calladj,calltherm,n2cond,callsoil)
     8      logical,save :: callconduct,callmolvis,callmoldiff
     9!$OMP THREADPRIVATE(callconduct,callmolvis,callmoldiff)
    810      logical,save :: season,diurnal,lwrite
    911!$OMP THREADPRIVATE(season,diurnal,lwrite)
     
    204206      real,save    :: alpha_top ! cooling constant at top of atmosphere
    205207      real,save    :: pref      ! pressure at mid transition fo alpha_top (Pa)
    206       real,save    :: deltap    ! width of transition to alpha_top (Pa) 
     208      real,save    :: deltap    ! width of transition to alpha_top (Pa)
    207209!$OMP THREADPRIVATE(alpha_top,pref,deltap)
    208      
     210
    209211
    210212      integer,save :: iddist
  • trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3439 r3455  
    406406     if (is_master) write(*,*)trim(rname)//": alpha_soil = ",alpha_soil
    407407
    408 ! Slab Ocean !AF24: removed
    409 
    410408! Chemistry in the thermosphere
    411409     if (is_master) write(*,*) trim(rname)//": Use deposition ?"
     
    418416     call getin_p("haze",haze)
    419417     if (is_master) write(*,*)trim(rname)//": haze = ",haze
     418
     419
     420
     421      if (is_master) write(*,*)trim(rname)// "call thermal conduction ?"
     422      callconduct=.false. ! default value
     423      call getin_p("callconduct",callconduct)
     424      if (is_master) write(*,*)trim(rname)// " callconduct = ",callconduct
     425
     426      if (is_master) write(*,*)trim(rname)// "call phitop ?"
     427      phitop=0. ! default value
     428      call getin_p("phitop",phitop)
     429      if (is_master) write(*,*)trim(rname)// " phitop = ",phitop
     430
     431      if (is_master) write(*,*)trim(rname)// "call molecular viscosity ?"
     432      callmolvis=.false. ! default value
     433      call getin_p("callmolvis",callmolvis)
     434      if (is_master) write(*,*)trim(rname)// " callmolvis = ",callmolvis
     435
     436      if (is_master) write(*,*)trim(rname)// "call molecular diffusion ?"
     437      callmoldiff=.false. ! default value
     438      call getin_p("callmoldiff",callmoldiff)
     439      if (is_master) write(*,*)trim(rname)// " callmoldiff = ",callmoldiff
    420440
    421441! Global1D mean and solar zenith angle
     
    14411461     if ((.not.tracer).and.(haze)) then
    14421462       call abort_physic(rname, 'if haze are on, tracers must be on!', 1)
    1443 
    1444      endif
    1445      if (callgasvis.and..not.callsoil) then
    1446          call abort_physic(rname, 'if callgasvis is set, callsoil must be true', 1)
    1447 
    1448      endif       
     1463     endif
     1464     if (callmolvis.and..not.callconduct) then
     1465         call abort_physic(rname, 'if callmolvis is set, callconduct must be true', 1)
     1466     endif
    14491467     if (paleo.and..not.fast) then
    14501468         call abort_physic(rname, 'if paleo is set, fast must be true', 1)
    1451 
    1452      endif       
     1469     endif
    14531470     if ((haze_proffix.or.haze_radproffix).and..not.aerohaze) then
    14541471         call abort_physic(rname, 'for now, haze/rad proffix only works w aerohaze=T', 1)
    1455 
    1456      endif   
     1472     endif
    14571473      if (condcosurf.and.no_n2frost) then
    14581474        call abort_physic(rname, "CO surface condensation and no_n2frost are both active which may not be relevant", 1)
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3453 r3455  
    4646      use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp
    4747      use time_phylmdz_mod, only: daysec
    48       use callkeys_mod, only: albedo_spectral_mode, calladj, calldifv, &
    49                               callrad, callsoil, nosurf, &
    50                               aerohaze, corrk, diagdtau,&
    51                               diurnal, enertest, fat1au, &
    52                               icetstep, intheat, iradia, kastprof, &
    53                               lwrite, mass_redistrib, meanOLR, &
    54                               fast,fasthaze,haze,metcloud,monoxcloud,&
    55                               n2cond,nearn2cond,noseason_day,conservn2, &
     48      use callkeys_mod, only: albedo_spectral_mode, calladj, calldifv,        &
     49                              callrad, callsoil, nosurf,                      &
     50                              callconduct,callmolvis,callmoldiff,             &
     51                              aerohaze, corrk, diagdtau,                      &
     52                              diurnal, enertest, fat1au,                      &
     53                              icetstep, intheat, iradia, kastprof,            &
     54                              lwrite, mass_redistrib, meanOLR,                &
     55                              fast,fasthaze,haze,metcloud,monoxcloud,         &
     56                              n2cond,nearn2cond,noseason_day,conservn2,       &
    5657                              convergeps,kbo,triton,paleo,paleoyears,glaflow, &
    57                               carbox, methane,condmetsurf,condcosurf,&
    58                               oldplutovdifc,oldplutocorrk,oldplutosedim, &
    59                               aerohaze,haze_proffix,haze_radproffix,&
    60                               source_haze, tsurfmax, albmin_ch4, &
    61                               season, sedimentation,generic_condensation, &
    62                               specOLR, &
    63                               startphy_file, testradtimes, &
    64                               tracer, UseTurbDiff, &
     58                              carbox, methane,condmetsurf,condcosurf,         &
     59                              oldplutovdifc,oldplutocorrk,oldplutosedim,      &
     60                              aerohaze,haze_proffix,haze_radproffix,          &
     61                              source_haze, tsurfmax, albmin_ch4,              &
     62                              season, sedimentation,generic_condensation,     &
     63                              specOLR,                                        &
     64                              startphy_file, testradtimes,                    &
     65                              tracer, UseTurbDiff,                            &
    6566                              global1d, szangle
    6667      use generic_tracer_index_mod, only: generic_tracer_index
     
    376377      REAL zdqflow(ngrid,nq)
    377378
     379      REAL zdtconduc(ngrid,nlayer) ! (K/s)
     380      REAL zdumolvis(ngrid,nlayer)
     381      REAL zdvmolvis(ngrid,nlayer)
     382      real zdqmoldiff(ngrid,nlayer,nq)
     383
    378384      ! Haze relatated tendancies
    379385      REAL zdqhaze(ngrid,nlayer,nq)
     
    860866         call testconservmass(ngrid,nlayer,pplev(:,1),qsurf(:,1))
    861867      endif
     868
     869
     870
     871! --------------------------------------------------------
     872!    1.3 thermosphere
     873! --------------------------------------------------------
     874
     875! ajout de la conduction depuis la thermosphere
     876      IF (callconduct) THEN
     877
     878          call conduction (ngrid,nlayer,ptimestep, &
     879                      pplay,pt,zzlay,zzlev,zdtconduc,tsurf)
     880          DO l=1,nlayer
     881             DO ig=1,ngrid
     882                pdt(ig,l)=pdt(ig,l)+ zdtconduc(ig,l)
     883             ENDDO
     884          ENDDO
     885
     886      ENDIF
     887
     888! ajout de la viscosite moleculaire
     889      IF (callmolvis) THEN
     890          call molvis(ngrid,nlayer,ptimestep,   &
     891                      pplay,pt,zzlay,zzlev,  &
     892                      zdtconduc,pu,tsurf,zdumolvis)
     893          call molvis(ngrid,nlayer,ptimestep,   &
     894                      pplay,pt,zzlay,zzlev,  &
     895                      zdtconduc,pv,tsurf,zdvmolvis)
     896
     897          DO l=1,nlayer
     898             DO ig=1,ngrid
     899             ! pdt(ig,l)=pdt(ig,l)+ zdtconduc(ig,l)
     900                pdv(ig,l)=pdv(ig,l)+zdvmolvis(ig,l)
     901                pdu(ig,l)=pdu(ig,l)+zdumolvis(ig,l)
     902             ENDDO
     903          ENDDO
     904      ENDIF
     905
     906      IF (callmoldiff) THEN
     907           call moldiff_red(ngrid,nlayer,nq, &
     908                        pplay,pplev,pt,pdt,pq,pdq,ptimestep,   &
     909                        zzlay,zdtconduc,zdqmoldiff)
     910
     911           DO l=1,nlayer
     912              DO ig=1,ngrid
     913                 DO iq=1, nq
     914                  pdq(ig,l,iq)=pdq(ig,l,iq)+zdqmoldiff(ig,l,iq)
     915                 ENDDO
     916              ENDDO
     917           ENDDO
     918      ENDIF
     919
     920      if (conservn2) then
     921         write(*,*) 'conservn2 thermo'
     922         call testconservmass(ngrid,nlayer,pplev(:,1),qsurf(:,1))
     923      endif
     924
    862925
    863926!---------------------------------
  • trunk/LMDZ.PLUTO/libf/phypluto/surfdat_h.F90

    r3275 r3455  
    1616       real,allocatable,dimension(:) :: zmea,zstd,zsig,zgam,zthe
    1717!$OMP THREADPRIVATE(zmea,zstd,zsig,zgam,zthe)
     18       real phitop ! heatflux at top of atmosphere? for Triton !AF24
    1819       real ttop
    1920       real,allocatable,dimension(:) :: kp ! TB ref pressure
    2021       real p00
    21 !$OMP THREADPRIVATE(ttop,kp,p00)
     22!$OMP THREADPRIVATE(phitop,ttop,kp,p00)
    2223! surface properties ! TB16
    2324       real alb_n2b,alb_n2a,alb_ch4,alb_co,alb_tho,emis_n2b,emis_n2a
  • trunk/LMDZ.PLUTO/libf/phypluto/tabfi_mod.F90

    r3453 r3455  
    1212!   C. Hourdin 15/11/96
    1313!
    14 !   Object:        Lecture du tab_cntrl physique dans un fichier 
     14!   Object:        Lecture du tab_cntrl physique dans un fichier
    1515!   ------            et initialisation des constantes physiques
    1616!
     
    2121!     ------
    2222!
    23 !      - nid:    unitne logique du fichier ou on va lire le tab_cntrl   
    24 !                      (ouvert dans le programme appellant) 
     23!      - nid:    unitne logique du fichier ou on va lire le tab_cntrl
     24!                      (ouvert dans le programme appellant)
    2525!
    2626!                 si nid=0:
    2727!                       pas de lecture du tab_cntrl mais
    2828!                       Valeurs par default des constantes physiques
    29 !       
    30 !      - tab0:    Offset de tab_cntrl a partir duquel sont ranges 
     29!
     30!      - tab0:    Offset de tab_cntrl a partir duquel sont ranges
    3131!                  les parametres physiques (50 pour start_archive)
    3232!
     
    4444!      - p_rad
    4545!      - p_omeg   !
    46 !      - p_g      ! Constantes physiques ayant des 
     46!      - p_g      ! Constantes physiques ayant des
    4747!      - p_mugaz  ! homonymes dynamiques
    4848!      - p_daysec !
     
    5858      use mod_phys_lmdz_para, only: is_parallel
    5959      use planete_mod, only: year_day, periastr, apoastr, peri_day, &
    60                              obliquit, z0, lmixmin, emin_turb
     60                             obliquit, z0, lmixmin, emin_turb, &
     61                             tpal, adjust
    6162      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
    6263      use time_phylmdz_mod, only: dtphys, daysec
    6364      use callkeys_mod, only: cpp_mugaz_mode
    6465      implicit none
    65  
     66
    6667      include "netcdf.inc"
    6768
     
    8788      LOGICAL :: found
    8889      CHARACTER(len=5) :: modname="tabfi"
    89      
     90
    9091      write(*,*)"tabfi: nid=",nid," tab0=",tab0," Lmodif=",Lmodif
    9192
     
    9798        lmax=0 ! not used anyways
    9899        !day_ini already set via inifis
    99         time=0 
     100        time=0
    100101! Informations about planet for dynamics and physics
    101102        ! rad,cpp,g,r,rcp already initialized by inifis
     
    219220      p_rad=rad
    220221
    221       ENDIF    ! end of (nid = 0) 
     222      ENDIF    ! end of (nid = 0)
    222223
    223224!-----------------------------------------------------------------------
    224225!       Write physical constants to output before modifying them
    225226!-----------------------------------------------------------------------
    226  
     227
    227228   6  FORMAT(a20,e15.6,e15.6)
    228229   5  FORMAT(a20,f12.2,f12.2)
    229  
     230
    230231      write(*,*) '*****************************************************'
    231232      write(*,*) 'Reading tab_cntrl when calling tabfi before changes'
     
    306307      write(*,*) '(10)     daysec   : length of a sol (s)'
    307308      write(*,*)
    308  
    309  
     309
     310
    310311      do while(modif(1:1).ne.'hello')
    311312        write(*,*)
     
    316317        read(*,fmt='(a20)') modif
    317318        if (modif(1:1) .eq. ' ') goto 999
    318  
     319
    319320        write(*,*)
    320321        write(*,*) modif(1:len_trim(modif)) , ' : '
     
    365366 106      read(*,*,iostat=ierr) emisice(1)
    366367          if(ierr.ne.0) goto 106
    367           write(*,*) 
     368          write(*,*)
    368369          write(*,*) ' emisice(1) (new value):',emisice(1)
    369370          write(*,*)
     
    373374 107      read(*,*,iostat=ierr) emisice(2)
    374375          if(ierr.ne.0) goto 107
    375           write(*,*) 
     376          write(*,*)
    376377          write(*,*) ' emisice(2) (new value):',emisice(2)
    377378
     
    381382 110      read(*,*,iostat=ierr) iceradius(1)
    382383          if(ierr.ne.0) goto 110
    383           write(*,*) 
     384          write(*,*)
    384385          write(*,*) ' iceradius(1) (new value):',iceradius(1)
    385386          write(*,*)
     
    389390 111      read(*,*,iostat=ierr) iceradius(2)
    390391          if(ierr.ne.0) goto 111
    391           write(*,*) 
     392          write(*,*)
    392393          write(*,*) ' iceradius(2) (new value):',iceradius(2)
    393394
     
    397398 112      read(*,*,iostat=ierr) dtemisice(1)
    398399          if(ierr.ne.0) goto 112
    399           write(*,*) 
     400          write(*,*)
    400401          write(*,*) ' dtemisice(1) (new value):',dtemisice(1)
    401402          write(*,*)
     
    405406 113      read(*,*,iostat=ierr) dtemisice(2)
    406407          if(ierr.ne.0) goto 113
    407           write(*,*) 
     408          write(*,*)
    408409          write(*,*) ' dtemisice(2) (new value):',dtemisice(2)
    409410
     
    414415 115      read(*,*,iostat=ierr) obliquit
    415416          if(ierr.ne.0) goto 115
    416           write(*,*) 
     417          write(*,*)
    417418          write(*,*) ' obliquit (new value):',obliquit
    418419
     
    423424 116      read(*,*,iostat=ierr) peri_day
    424425          if(ierr.ne.0) goto 116
    425           write(*,*) 
     426          write(*,*)
    426427          write(*,*) ' peri_day (new value):',peri_day
    427428
     
    432433 117      read(*,*,iostat=ierr) periastr
    433434          if(ierr.ne.0) goto 117
    434           write(*,*) 
     435          write(*,*)
    435436          write(*,*) ' periastr (new value):',periastr
    436  
     437
    437438        else if (modif(1:len_trim(modif)) .eq. 'apoastr') then
    438439          write(*,*) 'current value:',apoastr
     
    441442 118      read(*,*,iostat=ierr) apoastr
    442443          if(ierr.ne.0) goto 118
    443           write(*,*) 
     444          write(*,*)
    444445          write(*,*) ' apoastr (new value):',apoastr
    445  
     446
    446447        else if (modif(1:len_trim(modif)) .eq. 'volcapa') then
    447448          write(*,*) 'current value:',volcapa
     
    449450 119      read(*,*,iostat=ierr) volcapa
    450451          if(ierr.ne.0) goto 119
    451           write(*,*) 
     452          write(*,*)
    452453          write(*,*) ' volcapa (new value):',volcapa
    453        
     454
    454455        else if (modif(1:len_trim(modif)).eq.'rad') then
    455456          write(*,*) 'current value:',rad
     
    457458 120      read(*,*,iostat=ierr) rad
    458459          if(ierr.ne.0) goto 120
    459           write(*,*) 
     460          write(*,*)
    460461          write(*,*) ' rad (new value):',rad
    461462
     
    465466 121      read(*,*,iostat=ierr) omeg
    466467          if(ierr.ne.0) goto 121
    467           write(*,*) 
     468          write(*,*)
    468469          write(*,*) ' omeg (new value):',omeg
    469        
     470
    470471        else if (modif(1:len_trim(modif)).eq.'g') then
    471472          write(*,*) 'current value:',g
     
    473474 122      read(*,*,iostat=ierr) g
    474475          if(ierr.ne.0) goto 122
    475           write(*,*) 
     476          write(*,*)
    476477          write(*,*) ' g (new value):',g
    477478
     
    481482 123      read(*,*,iostat=ierr) mugaz
    482483          if(ierr.ne.0) goto 123
    483           write(*,*) 
     484          write(*,*)
    484485          write(*,*) ' mugaz (new value):',mugaz
    485486          r=8.314511/(mugaz/1000.0)
     
    491492 124      read(*,*,iostat=ierr) rcp
    492493          if(ierr.ne.0) goto 124
    493           write(*,*) 
     494          write(*,*)
    494495          write(*,*) ' rcp (new value):',rcp
    495496          r=8.314511/(mugaz/1000.0)
     
    502503          call su_gases
    503504          call calc_cpp_mugaz
    504           write(*,*) 
     505          write(*,*)
    505506          write(*,*) ' cpp (new value):',cpp
    506507          write(*,*) ' mugaz (new value):',mugaz
     
    508509          rcp=r/cpp
    509510          write(*,*) ' rcp (new value):',rcp
    510          
     511
    511512        else if (modif(1:len_trim(modif)).eq.'daysec') then
    512513          write(*,*) 'current value:',daysec
     
    514515 125      read(*,*,iostat=ierr) daysec
    515516          if(ierr.ne.0) goto 125
    516           write(*,*) 
     517          write(*,*)
    517518          write(*,*) ' daysec (new value):',daysec
    518519
     
    520521        else if (modif(1:len_trim(modif)).eq.'year_day') then
    521522          write(*,*) 'current value:',year_day
    522           write(*,*) 'enter new value:' 
     523          write(*,*) 'enter new value:'
    523524 126      read(*,*,iostat=ierr) year_day
    524525          if(ierr.ne.0) goto 126
     
    534535!       Write values of physical constants after modifications
    535536!-----------------------------------------------------------------------
    536  
     537
    537538      write(*,*) '*****************************************************'
    538539      write(*,*) 'Reading tab_cntrl when calling tabfi AFTER changes'
     
    548549      write(*,5) '(9)             rcp',tab_cntrl(tab0+9),rcp
    549550      write(*,6) '(11)        dtphys?',tab_cntrl(tab0+11),dtphys
    550  
     551
    551552      write(*,5) '(14)       year_day',tab_cntrl(tab0+14),year_day
    552553      write(*,5) '(15)       periastr',tab_cntrl(tab0+15),periastr
     
    554555      write(*,5) '(17)       peri_day',tab_cntrl(tab0+17),peri_day
    555556      write(*,5) '(18)       obliquit',tab_cntrl(tab0+18),obliquit
    556  
     557
    557558      write(*,6) '(19)             z0',tab_cntrl(tab0+19),z0
    558559      write(*,6) '(21)      emin_turb',tab_cntrl(tab0+21),emin_turb
    559560      write(*,5) '(20)        lmixmin',tab_cntrl(tab0+20),lmixmin
    560  
     561
    561562      write(*,5) '(26)        emissiv',tab_cntrl(tab0+26),emissiv
    562563      write(*,5) '(24)     emisice(1)',tab_cntrl(tab0+24),emisice(1)
     
    566567      write(*,5) '(33)   dtemisice(1)',tab_cntrl(tab0+33),dtemisice(1)
    567568      write(*,5) '(34)   dtemisice(2)',tab_cntrl(tab0+34),dtemisice(2)
    568  
     569
    569570      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
    570571
    571       write(*,*) 
    572       write(*,*) 
     572      write(*,*)
     573      write(*,*)
    573574
    574575      ENDIF ! of if (Lmodif == 1)
Note: See TracChangeset for help on using the changeset viewer.