Changeset 1790
- Timestamp:
- Sep 29, 2017, 1:57:44 PM (7 years ago)
- Location:
- trunk/LMDZ.TITAN
- Files:
-
- 1 added
- 6 deleted
- 4 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/deftank/callphys.def
r1681 r1790 95 95 Fat1AU = 1366.0 96 96 97 ## Tracer and aerosol options98 ## ~~~~~~~~~~~~~~~~~~~~~~~~~~99 # Gravitational sedimentation of tracers (just H2O ice for now) ?100 sedimentation = .false.101 102 97 ## Other physics options 103 98 ## ~~~~~~~~~~~~~~~~~~~~~ -
trunk/LMDZ.TITAN/libf/dyn3d/disvert.F
r1621 r1790 3 3 ! to use 'getin' 4 4 USE ioipsl_getincom 5 USE callkeys_mod, ONLY: kastprof,pceil5 USE callkeys_mod, ONLY: pceil 6 6 USE comvert_mod, ONLY: ap,bp,sig,nivsigs,nivsig,pa,preff, 7 7 . aps,bps,presnivs,pseudoalt,scaleheight … … 64 64 write(*,*) " autozlevs = ", autozlevs 65 65 66 write(*,*)"Operate in kastprof mode?"67 kastprof=.false.68 call getin("kastprof",kastprof)69 write(*,*)" kastprof = ",kastprof70 71 print*,'kast=',kastprof72 73 66 pceil=100.0 ! Pascals 74 67 PRINT *,'Ceiling pressure (Pa) ?' … … 81 74 endif 82 75 83 if(kastprof.and.iim.gt.1)then84 print*,'kastprof no good in 3D...'85 call abort86 endif87 88 76 psurf=610. ! default value for psurf 89 77 PRINT *,'Surface pressure (Pa) ?' … … 91 79 write(*,*) " psurf = ",psurf 92 80 93 if(kastprof)then 94 95 sig(1)=1 96 do l=2,llm 97 !sig(l)=1. - real(l-1)/real(llm) ! uses linear sigma spacing 98 !sig(l)=exp(-real(l-1)*h/real(llm)) ! uses log sigma spacing 99 !sig(l)=exp(-real(l-1)*Hmax/real(llm)) ! uses log sigma spacing 100 sig(l)=(pceil/psurf)**(real(l-1)/real(llm)) ! uses log sigma spacing 101 102 end do 103 sig(llm+1)=0 104 105 elseIF(ierr4.eq.0)then 81 IF(ierr4.eq.0)then 106 82 PRINT*,'****************************' 107 83 PRINT*,'Lecture de z2sig.def' -
trunk/LMDZ.TITAN/libf/dyn3d/logic_mod.F90
r1593 r1790 3 3 IMPLICIT NONE 4 4 5 LOGICAL purmats,forward,leapf,apphys,statcl,conser, & 6 & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus,hybrid,autozlevs 5 LOGICAL purmats ! true if time stepping is purely Matsuno scheme 6 ! false implies Matsuno-Leapfrog time stepping scheme 7 LOGICAL forward ! true if during forward phase of Matsuno step 8 LOGICAL leapf ! true if during a leapfrog time stepping step 9 LOGICAL apphys ! true if during a time step when physics will be called 10 LOGICAL statcl 11 LOGICAL conser 12 LOGICAL apdiss ! true if during a time step when dissipation will be called 13 LOGICAL apdelq 14 LOGICAL saison 15 LOGICAL ecripar 16 LOGICAL fxyhypb ! true if using hyperbolic function discretization 17 ! for latitudinal grid 18 LOGICAL ysinus ! true if using sine function discretiation 19 ! for latitudinal grid 20 LOGICAL read_start ! true if reading a start.nc file to initialize fields 21 LOGICAL ok_guide ! true if nudging 22 LOGICAL ok_strato 23 LOGICAL tidal ! true if adding tidal forces (for Titan) 24 LOGICAL ok_gradsfile 25 LOGICAL ok_limit ! true for boundary conditions file creation (limit.nc) 26 LOGICAL ok_etat0 ! true for initial states creation (start.nc, startphy.nc) 27 LOGICAL read_orop ! true for sub-cell scales orographic params read in file 28 LOGICAL hybrid ! vertical coordinate is hybrid if true (sigma otherwise) 29 ! (only used if disvert_type==2) 30 LOGICAL autozlevs ! true if auto-discretization of vertical levels 31 LOGICAL moyzon_mu,moyzon_ch ! used for zonal averages in Titan 7 32 8 INTEGER iflag_phys ! ==1 if calling a physics package 33 INTEGER iflag_phys ! type of physics to call: 0 none, 1: phy*** package, 34 ! 2: Held & Suarez, 101-200: aquaplanets & terraplanets 35 INTEGER iflag_trac 9 36 10 37 END MODULE logic_mod -
trunk/LMDZ.TITAN/libf/phytitan/dyn1d/rcm1d.F
r1621 r1790 6 6 use mod_grid_phy_lmdz, only : regular_lonlat 7 7 use infotrac, only: nqtot, tname 8 use surfdat_h, only: albedodat, phisfi, dryness, watercaptag,8 use surfdat_h, only: albedodat, phisfi, 9 9 & zmea, zstd, zsig, zgam, zthe, 10 10 & emissiv, emisice, iceradius, … … 14 14 use phyredem, only: physdem0,physdem1 15 15 use geometry_mod, only: init_geometry 16 use slab_ice_h, only: noceanmx17 16 use planete_mod, only: apoastr,periastr,year_day,peri_day, 18 17 & obliquit,nres,z0,lmixmin,emin_turb,coefvis,coefir, … … 23 22 & nday, iphysiq 24 23 use callkeys_mod, only: tracer,check_cpp_match,rings_shadow, 25 & specOLR, water,pceil,ok_slab_ocean24 & specOLR,pceil 26 25 USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff, sig, 27 26 & presnivs,pseudoalt,scaleheight … … 58 57 ! A. Spiga 59 58 ! J. Leconte (2012) 59 ! J. Vatant d'Ollone (2017) 60 60 ! 61 61 !================================================================== … … 88 88 REAL,ALLOCATABLE :: qsurf(:) ! tracer surface budget (e.g. kg.m-2) 89 89 REAL,ALLOCATABLE :: tsoil(:) ! subsurface soil temperature (K) 90 ! REAL co2ice ! co2ice layer (kg.m-2) !not used anymore91 integer :: i_co2_ice=0 ! tracer index of co2 ice92 integer :: i_h2o_ice=0 ! tracer index of h2o ice93 integer :: i_h2o_vap=0 ! tracer index of h2o vapor94 90 REAL emis(1) ! surface layer 95 91 REAL q2(llm+1) ! Turbulent Kinetic Energy … … 112 108 integer :: nq !=1 ! number of tracers 113 109 114 character*2 str2115 character (len=7) :: str7116 110 character(len=44) :: txt 117 111 118 logical oldcompare, earthhack,saveprofile112 logical saveprofile 119 113 120 114 ! added by RW for zlay computation … … 125 119 real logplevs(llm) 126 120 127 ! added by BC 128 REAL cloudfrac(1,llm) 129 REAL hice(1),totcloudfrac(1) 130 131 ! added by BC for ocean 132 real rnat(1) 133 REAL tslab(1,noceanmx),tsea_ice(1),sea_ice(1) 134 real pctsrf_sic(1) 135 136 121 ! added by JVO 122 REAL tankCH4(1) 137 123 138 124 ! added by AS to avoid the use of adv trac common … … 157 143 IF (.not. ALLOCATED(zgam)) ALLOCATE(zgam(1)) 158 144 IF (.not. ALLOCATED(zthe)) ALLOCATE(zthe(1)) 159 IF (.not. ALLOCATED(dryness)) ALLOCATE(dryness(1))160 IF (.not. ALLOCATED(watercaptag)) ALLOCATE(watercaptag(1))161 145 !! those are defined in comdiurn_h.F90 162 146 IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(1)) … … 272 256 endif 273 257 enddo !of do iq=1,nq 274 ! check for co2_ice / h2o_ice tracers:275 i_co2_ice=0276 i_h2o_ice=0277 i_h2o_vap=0278 do iq=1,nq279 if (tname(iq)=="co2_ice") then280 i_co2_ice=iq281 elseif (tname(iq)=="h2o_ice") then282 i_h2o_ice=iq283 elseif (tname(iq)=="h2o_vap") then284 i_h2o_vap=iq285 endif286 enddo287 258 else 288 259 write(*,*) 'Cannot find required file "traceur.def"' … … 577 548 write(*,*)" tracer:",trim(txt) 578 549 579 ! CO2580 if (txt.eq."co2_ice") then581 q(:,iq)=0. ! kg/kg of atmosphere582 qsurf(iq)=0. ! kg/m2 at the surface583 ! Look for a "profile_co2_ice" input file584 open(91,file='profile_co2_ice',status='old',585 & form='formatted',iostat=ierr)586 if (ierr.eq.0) then587 read(91,*) qsurf(iq)588 do ilayer=1,nlayer589 read(91,*) q(ilayer,iq)590 enddo591 else592 write(*,*) "No profile_co2_ice file!"593 endif594 close(91)595 endif ! of if (txt.eq."co2")596 597 ! WATER VAPOUR598 if (txt.eq."h2o_vap") then599 q(:,iq)=0. ! kg/kg of atmosphere600 qsurf(iq)=0. ! kg/m2 at the surface601 ! Look for a "profile_h2o_vap" input file602 open(91,file='profile_h2o_vap',status='old',603 & form='formatted',iostat=ierr)604 if (ierr.eq.0) then605 read(91,*) qsurf(iq)606 do ilayer=1,nlayer607 read(91,*) q(ilayer,iq)608 enddo609 else610 write(*,*) "No profile_h2o_vap file!"611 endif612 close(91)613 endif ! of if (txt.eq."h2o_vap")614 615 ! WATER ICE616 if (txt.eq."h2o_ice") then617 q(:,iq)=0. ! kg/kg of atmosphere618 qsurf(iq)=0. ! kg/m2 at the surface619 ! Look for a "profile_h2o_ice" input file620 open(91,file='profile_h2o_ice',status='old',621 & form='formatted',iostat=ierr)622 if (ierr.eq.0) then623 read(91,*) qsurf(iq)624 do ilayer=1,nlayer625 read(91,*) q(ilayer,iq)626 enddo627 else628 write(*,*) "No profile_h2o_ice file!"629 endif630 close(91)631 endif ! of if (txt.eq."h2o_ice")632 633 550 enddo ! of do iq=1,nq 634 551 … … 673 590 emissiv=emis(1) ! we do this so that condense_co2 sets things to the right 674 591 ! value if there is no snow 675 676 if(i_co2_ice.gt.0)then677 qsurf(i_co2_ice)=0 ! default value for co2ice678 print*,'Initial CO2 ice on the surface (kg.m-2)'679 call getin("co2ice",qsurf(i_co2_ice))680 write(*,*) " co2ice = ",qsurf(i_co2_ice)681 IF (qsurf(i_co2_ice).ge.1.E+0) THEN682 ! if we have some CO2 ice on the surface, change emissivity683 if (latitude(1).ge.0) then ! northern hemisphere684 emis(1)=emisice(1)685 else ! southern hemisphere686 emis(1)=emisice(2)687 endif688 ENDIF689 endif690 592 691 593 c calcul des pressions et altitudes en utilisant les niveaux sigma … … 823 725 824 726 825 ! Initialize slab ocean826 ! -----------------827 rnat=1. ! default value for rnat828 if(inertiedat(1,1).GE.10000.)then829 rnat=0.830 endif831 if(ok_slab_ocean)then832 rnat=0.833 tslab(1,1)=tsurf(1)834 tslab(1,2)=tsurf(1)835 tsea_ice=tsurf836 pctsrf_sic=0.837 sea_ice=0.838 endif839 840 841 842 727 c Write a "startfi" file 843 728 c -------------------- … … 850 735 call physdem1("startfi.nc",nsoilmx,1,llm,nq, 851 736 & dtphys,time, 852 & tsurf,tsoil,emis,q2,qsurf, 853 & cloudfrac,totcloudfrac,hice, 854 & rnat,pctsrf_sic,tslab,tsea_ice,sea_ice) 737 & tsurf,tsoil,emis,q2,qsurf,tankCH4) 855 738 856 739 c=======================================================================
Note: See TracChangeset
for help on using the changeset viewer.