Ignore:
Timestamp:
Mar 29, 2016, 11:45:49 AM (9 years ago)
Author:
emillour
Message:

All GCMS:
More updates to enforce dynamics/physics separation:

get rid of references to "temps_mod" from physics packages;
make a "time_phylmdz_mod.F90" module to store that
information and fill it via "iniphysiq".

EM

Location:
trunk/LMDZ.GENERIC/libf
Files:
1 added
1 deleted
15 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/dynlonlat_phylonlat/phystd/iniphysiq_mod.F90

    r1523 r1524  
    2424use planete_mod, only: ini_planete_mod
    2525USE comvert_mod, ONLY: ap,bp,preff
     26use inifis_mod, only: inifis
    2627use regular_lonlat_mod, only: init_regular_lonlat, &
    2728                              east, west, north, south, &
  • trunk/LMDZ.GENERIC/libf/dynlonlat_phylonlat/phystd/newstart.F

    r1470 r1524  
    2222      USE comgeomfi_h, ONLY: lati, long, area
    2323      use datafile_mod, only: datadir, surfdir
    24 ! to use  'getin'
    25 !      USE ioipsl_getincom, only: getin
    26       USE ioipsl_getincom_p, only: getin_p
     24      use ioipsl_getin_p_mod, only: getin_p
    2725      use control_mod, only: day_step, iphysiq, anneeref, planet_type
    2826      use phyredem, only: physdem0, physdem1
     
    3735      USE temps_mod, ONLY: day_ini
    3836      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     37      use inifis_mod, only: inifis
    3938      implicit none
    4039
  • trunk/LMDZ.GENERIC/libf/phystd/comcstfi_mod.F90

    r1520 r1524  
    88      REAL,SAVE :: cpp ! Cp of the atmosphere
    99      REAL,SAVE :: rcp ! r/cpp
    10       REAL,SAVE :: dtphys ! physics time step (s)
    11       REAL,SAVE :: daysec ! length of day (s)
    1210      REAL,SAVE :: mugaz ! molar mass of the atmosphere (g/mol)
    1311      REAL,SAVE :: omeg ! planet rotation rate (rad/s)
    1412      REAL,SAVE :: avocado ! something like 6.022e23
    15 !$OMP THREADPRIVATE(pi,rad,g,r,cpp,rcp,dtphys,daysec,mugaz,omeg,avocado)
     13!$OMP THREADPRIVATE(pi,rad,g,r,cpp,rcp,mugaz,omeg,avocado)
    1614
    1715END MODULE comcstfi_mod
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r1494 r1524  
    1919     &         obliquit,nres,z0,lmixmin,emin_turb,coefvis,coefir,
    2020     &         timeperi,e_elips,p_elips
    21       use comcstfi_mod, only: pi, cpp, daysec, dtphys, rad, g, r,
     21      use comcstfi_mod, only: pi, cpp, rad, g, r,
    2222     &                        mugaz, rcp, omeg
     23      use time_phylmdz_mod, only: daysec, dtphys
    2324      use callkeys_mod, only: tracer,check_cpp_match,rings_shadow,
    24      &          specOLR,water,pceil,ok_slab_ocean
     25     &                        specOLR,water,pceil,ok_slab_ocean
    2526      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff
    2627      USE logic_mod, ONLY: hybrid,autozlevs
     28      use inifis_mod, only: inifis
    2729      implicit none
    2830
     
    130132      character*20,allocatable :: nametrac(:)   ! name of the tracer (no need for adv trac common)
    131133
    132       real :: latitude, longitude
     134      real :: latitude(1), longitude(1)
    133135
    134136c=======================================================================
     
    339341      longitude=longitude*pi/180.E+0
    340342
     343
     344!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     345!!!! PLANETARY CONSTANTS !!!!
     346!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     347
     348      g = -99999.
     349      PRINT *,'GRAVITY in m s-2 ?'
     350      call getin("g",g)
     351      IF (g.eq.-99999.) THEN
     352          PRINT *,"STOP. I NEED g IN RCM1D.DEF."
     353          STOP
     354      ELSE
     355          PRINT *,"--> g = ",g
     356      ENDIF
     357
     358      rad = -99999.
     359      PRINT *,'PLANETARY RADIUS in m ?'
     360      call getin("rad",rad)
     361      ! Planetary  radius is needed to compute shadow of the rings
     362      IF (rad.eq.-99999. .and. rings_shadow .eqv. .true.) THEN
     363          PRINT *,"STOP. I NEED rad IN RCM1D.DEF."
     364          STOP
     365      ELSE
     366          PRINT *,"--> rad = ",rad
     367      ENDIF
     368
     369      daysec = -99999.
     370      PRINT *,'LENGTH OF A DAY in s ?'
     371      call getin("daysec",daysec)
     372      IF (daysec.eq.-99999.) THEN
     373          PRINT *,"STOP. I NEED daysec IN RCM1D.DEF."
     374          STOP
     375      ELSE
     376          PRINT *,"--> daysec = ",daysec
     377      ENDIF
     378      omeg=4.*asin(1.)/(daysec)
     379      PRINT *,"OK. FROM THIS I WORKED OUT:"
     380      PRINT *,"--> omeg = ",omeg
     381
     382      year_day = -99999.
     383      PRINT *,'LENGTH OF A YEAR in days ?'
     384      call getin("year_day",year_day)
     385      IF (year_day.eq.-99999.) THEN
     386          PRINT *,"STOP. I NEED year_day IN RCM1D.DEF."
     387          STOP
     388      ELSE
     389          PRINT *,"--> year_day = ",year_day
     390      ENDIF
     391
     392      periastr = -99999.
     393      PRINT *,'MIN DIST STAR-PLANET in AU ?'
     394      call getin("periastr",periastr)
     395      IF (periastr.eq.-99999.) THEN
     396          PRINT *,"STOP. I NEED periastr IN RCM1D.DEF."
     397          STOP
     398      ELSE
     399          PRINT *,"--> periastr = ",periastr
     400      ENDIF
     401
     402      apoastr = -99999.
     403      PRINT *,'MAX DIST STAR-PLANET in AU ?'
     404      call getin("apoastr",apoastr)
     405      IF (apoastr.eq.-99999.) THEN
     406          PRINT *,"STOP. I NEED apoastr IN RCM1D.DEF."
     407          STOP
     408      ELSE
     409          PRINT *,"--> apoastr = ",apoastr
     410      ENDIF
     411
     412      peri_day = -99999.
     413      PRINT *,'DATE OF PERIASTRON in days ?'
     414      call getin("peri_day",peri_day)
     415      IF (peri_day.eq.-99999.) THEN
     416          PRINT *,"STOP. I NEED peri_day IN RCM1D.DEF."
     417          STOP
     418      ELSE IF (peri_day.gt.year_day) THEN
     419          PRINT *,"STOP. peri_day.gt.year_day"
     420          STOP
     421      ELSE 
     422          PRINT *,"--> peri_day = ", peri_day
     423      ENDIF
     424
     425      obliquit = -99999.
     426      PRINT *,'OBLIQUITY in deg ?'
     427      call getin("obliquit",obliquit)
     428      IF (obliquit.eq.-99999.) THEN
     429          PRINT *,"STOP. I NEED obliquit IN RCM1D.DEF."
     430          STOP
     431      ELSE
     432          PRINT *,"--> obliquit = ",obliquit
     433      ENDIF
     434
     435      psurf = -99999.
     436      PRINT *,'SURFACE PRESSURE in Pa ?'
     437      call getin("psurf",psurf)
     438      IF (psurf.eq.-99999.) THEN
     439          PRINT *,"STOP. I NEED psurf IN RCM1D.DEF."
     440          STOP
     441      ELSE
     442          PRINT *,"--> psurf = ",psurf
     443      ENDIF
     444      !! we need reference pressures
     445      pa=psurf/30.
     446      preff=psurf ! these values are not needed in 1D  (are you sure JL12)
     447
     448!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     449!!!! END PLANETARY CONSTANTS !!!!
     450!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     451
     452c  Date et heure locale du debut du run
     453c  ------------------------------------
     454c    Date (en sols depuis le solstice de printemps) du debut du run
     455      day0 = 0 ! default value for day0
     456      write(*,*) 'Initial date (in martian sols ; =0 at Ls=0)?'
     457      call getin("day0",day0)
     458      day=float(day0)
     459      write(*,*) " day0 = ",day0
     460c  Heure de demarrage
     461      time=0 ! default value for time
     462      write(*,*)'Initial local time (in hours, between 0 and 24)?'
     463      call getin("time",time)
     464      write(*,*)" time = ",time
     465      time=time/24.E+0 ! convert time (hours) to fraction of sol
     466
     467
     468c  Discretisation (Definition de la grille et des pas de temps)
     469c  --------------
     470c
     471      nlayer=llm
     472      nlevel=nlayer+1
     473      nsoil=nsoilmx
     474
     475      day_step=48 ! default value for day_step
     476      PRINT *,'Number of time steps per sol ?'
     477      call getin("day_step",day_step)
     478      write(*,*) " day_step = ",day_step
     479
     480       
     481      ecritphy=day_step ! default value for ecritphy
     482      PRINT *,'Nunber of steps between writediagfi ?'
     483      call getin("ecritphy",ecritphy)
     484      write(*,*) " ecritphy = ",ecritphy
     485
     486      ndt=10 ! default value for ndt
     487      PRINT *,'Number of sols to run ?'
     488      call getin("ndt",ndt)
     489      write(*,*) " ndt = ",ndt
     490
     491      ndt=ndt*day_step     
     492      dtphys=daysec/day_step 
     493      write(*,*)"-------------------------------------"
     494      write(*,*)"-------------------------------------"
     495      write(*,*)"--> Physical timestep is ",dtphys
     496      write(*,*)"-------------------------------------"
     497      write(*,*)"-------------------------------------"
     498
    341499!!! CALL INIFIS
    342500!!! - read callphys.def
     
    355513      r = 8.314511E+0 * 1000.E+0 / mugaz
    356514      rcp = r / cpp
    357 
    358 
    359 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    360 !!!! PLANETARY CONSTANTS !!!!
    361 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    362 
    363       g = -99999.
    364       PRINT *,'GRAVITY in m s-2 ?'
    365       call getin("g",g)
    366       IF (g.eq.-99999.) THEN
    367           PRINT *,"STOP. I NEED g IN RCM1D.DEF."
    368           STOP
    369       ELSE
    370           PRINT *,"--> g = ",g
    371       ENDIF
    372 
    373       rad = -99999.
    374       PRINT *,'PLANETARY RADIUS in m ?'
    375       call getin("rad",rad)
    376       ! Planetary  radius is needed to compute shadow of the rings
    377       IF (rad.eq.-99999. .and. rings_shadow .eqv. .true.) THEN
    378           PRINT *,"STOP. I NEED rad IN RCM1D.DEF."
    379           STOP
    380       ELSE
    381           PRINT *,"--> rad = ",rad
    382       ENDIF
    383 
    384       daysec = -99999.
    385       PRINT *,'LENGTH OF A DAY in s ?'
    386       call getin("daysec",daysec)
    387       IF (daysec.eq.-99999.) THEN
    388           PRINT *,"STOP. I NEED daysec IN RCM1D.DEF."
    389           STOP
    390       ELSE
    391           PRINT *,"--> daysec = ",daysec
    392       ENDIF
    393       omeg=4.*asin(1.)/(daysec)
    394       PRINT *,"OK. FROM THIS I WORKED OUT:"
    395       PRINT *,"--> omeg = ",omeg
    396 
    397       year_day = -99999.
    398       PRINT *,'LENGTH OF A YEAR in days ?'
    399       call getin("year_day",year_day)
    400       IF (year_day.eq.-99999.) THEN
    401           PRINT *,"STOP. I NEED year_day IN RCM1D.DEF."
    402           STOP
    403       ELSE
    404           PRINT *,"--> year_day = ",year_day
    405       ENDIF
    406 
    407       periastr = -99999.
    408       PRINT *,'MIN DIST STAR-PLANET in AU ?'
    409       call getin("periastr",periastr)
    410       IF (periastr.eq.-99999.) THEN
    411           PRINT *,"STOP. I NEED periastr IN RCM1D.DEF."
    412           STOP
    413       ELSE
    414           PRINT *,"--> periastr = ",periastr
    415       ENDIF
    416 
    417       apoastr = -99999.
    418       PRINT *,'MAX DIST STAR-PLANET in AU ?'
    419       call getin("apoastr",apoastr)
    420       IF (apoastr.eq.-99999.) THEN
    421           PRINT *,"STOP. I NEED apoastr IN RCM1D.DEF."
    422           STOP
    423       ELSE
    424           PRINT *,"--> apoastr = ",apoastr
    425       ENDIF
    426 
    427       peri_day = -99999.
    428       PRINT *,'DATE OF PERIASTRON in days ?'
    429       call getin("peri_day",peri_day)
    430       IF (peri_day.eq.-99999.) THEN
    431           PRINT *,"STOP. I NEED peri_day IN RCM1D.DEF."
    432           STOP
    433       ELSE IF (peri_day.gt.year_day) THEN
    434           PRINT *,"STOP. peri_day.gt.year_day"
    435           STOP
    436       ELSE 
    437           PRINT *,"--> peri_day = ", peri_day
    438       ENDIF
    439 
    440       obliquit = -99999.
    441       PRINT *,'OBLIQUITY in deg ?'
    442       call getin("obliquit",obliquit)
    443       IF (obliquit.eq.-99999.) THEN
    444           PRINT *,"STOP. I NEED obliquit IN RCM1D.DEF."
    445           STOP
    446       ELSE
    447           PRINT *,"--> obliquit = ",obliquit
    448       ENDIF
    449 
    450       psurf = -99999.
    451       PRINT *,'SURFACE PRESSURE in Pa ?'
    452       call getin("psurf",psurf)
    453       IF (psurf.eq.-99999.) THEN
    454           PRINT *,"STOP. I NEED psurf IN RCM1D.DEF."
    455           STOP
    456       ELSE
    457           PRINT *,"--> psurf = ",psurf
    458       ENDIF
    459       !! we need reference pressures
    460       pa=psurf/30.
    461       preff=psurf ! these values are not needed in 1D  (are you sure JL12)
    462 
    463 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    464 !!!! END PLANETARY CONSTANTS !!!!
    465 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    466 
    467 c  Date et heure locale du debut du run
    468 c  ------------------------------------
    469 c    Date (en sols depuis le solstice de printemps) du debut du run
    470       day0 = 0 ! default value for day0
    471       write(*,*) 'Initial date (in martian sols ; =0 at Ls=0)?'
    472       call getin("day0",day0)
    473       day=float(day0)
    474       write(*,*) " day0 = ",day0
    475 c  Heure de demarrage
    476       time=0 ! default value for time
    477       write(*,*)'Initial local time (in hours, between 0 and 24)?'
    478       call getin("time",time)
    479       write(*,*)" time = ",time
    480       time=time/24.E+0 ! convert time (hours) to fraction of sol
    481 
    482 
    483 c  Discretisation (Definition de la grille et des pas de temps)
    484 c  --------------
    485 c
    486       nlayer=llm
    487       nlevel=nlayer+1
    488       nsoil=nsoilmx
    489 
    490       day_step=48 ! default value for day_step
    491       PRINT *,'Number of time steps per sol ?'
    492       call getin("day_step",day_step)
    493       write(*,*) " day_step = ",day_step
    494 
    495        
    496       ecritphy=day_step ! default value for ecritphy
    497       PRINT *,'Nunber of steps between writediagfi ?'
    498       call getin("ecritphy",ecritphy)
    499       write(*,*) " ecritphy = ",ecritphy
    500 
    501       ndt=10 ! default value for ndt
    502       PRINT *,'Number of sols to run ?'
    503       call getin("ndt",ndt)
    504       write(*,*) " ndt = ",ndt
    505 
    506       ndt=ndt*day_step     
    507       dtphys=daysec/day_step 
    508       write(*,*)"-------------------------------------"
    509       write(*,*)"-------------------------------------"
    510       write(*,*)"--> Physical timestep is ",dtphys
    511       write(*,*)"-------------------------------------"
    512       write(*,*)"-------------------------------------"
    513515
    514516c output spectrum?
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r1521 r1524  
    1       SUBROUTINE inifis(ngrid,nlayer,nq,
    2      $           day_ini,pdaysec,ptimestep,
    3      $           plat,plon,parea,
    4      $           prad,pg,pr,pcpp)
    5 
    6       use radinc_h, only : naerkind
    7       use datafile_mod, only: datadir
    8       use comdiurn_h, only: sinlat, coslat, sinlon, coslon
    9       use comgeomfi_h, only: long, lati, area, totarea, totarea_planet
    10       use comsoil_h, only: ini_comsoil_h
    11       use control_mod, only: ecritphy
    12       use comcstfi_mod, only: rad, daysec, dtphys, cpp, g, r, rcp,
    13      &                        mugaz, pi, avocado
    14       use planete_mod, only: nres
    15       use planetwide_mod, only: planetwide_sumval
    16       use callkeys_mod
     1MODULE inifis_mod
     2IMPLICIT NONE
     3
     4CONTAINS
     5
     6  SUBROUTINE inifis(ngrid,nlayer,nq, &
     7             day_ini,pdaysec,ptimestep, &
     8             plat,plon,parea, &
     9             prad,pg,pr,pcpp)
     10
     11  use radinc_h, only : naerkind
     12  use datafile_mod, only: datadir
     13  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
     14  use comgeomfi_h, only: long, lati, area, totarea, totarea_planet
     15  use comsoil_h, only: ini_comsoil_h
     16  use control_mod, only: ecritphy
     17  use comcstfi_mod, only: rad, cpp, g, r, rcp, &
     18                          mugaz, pi, avocado
     19  use planete_mod, only: nres
     20  use planetwide_mod, only: planetwide_sumval
     21  use callkeys_mod
     22  use time_phylmdz_mod, only: init_time, daysec, dtphys
    1723
    1824!=======================================================================
     
    5157!   declarations:
    5258!   -------------
    53       use datafile_mod, only: datadir
    54       use ioipsl_getin_p_mod, only: getin_p
    55       IMPLICIT NONE
    56 
    57 
    58 
    59       REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
     59  use datafile_mod, only: datadir
     60  use ioipsl_getin_p_mod, only: getin_p
     61  IMPLICIT NONE
     62
     63
     64
     65  REAL,INTENT(IN) :: prad,pg,pr,pcpp,pdaysec,ptimestep
    6066 
    61       INTEGER,INTENT(IN) :: ngrid,nlayer,nq
    62       REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
    63       integer day_ini
    64       INTEGER ig,ierr
     67  INTEGER,INTENT(IN) :: ngrid,nlayer,nq
     68  REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
     69  integer,intent(in) :: day_ini
     70  INTEGER ig,ierr
    6571 
    66       EXTERNAL iniorbit,orbite
    67       EXTERNAL SSUM
    68       REAL SSUM
     72  EXTERNAL iniorbit,orbite
     73  EXTERNAL SSUM
     74  REAL SSUM
    6975 
    70       CHARACTER ch1*12
    71       CHARACTER ch80*80
    72 
    73       logical chem, h2o
    74       logical :: parameter, doubleq=.false.
    75 
    76       real psurf,pN2 ! added by RW for Gliese 581d N2+CO2
    77 
    78       rad=prad
    79       daysec=pdaysec
    80       dtphys=ptimestep
    81       cpp=pcpp
    82       g=pg
    83       r=pr
    84       rcp=r/cpp
    85 
    86       avocado = 6.02214179e23   ! added by RW
    87 
    88 
    89       ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
    90       ! (also done in dyn3d/defrun_new but not in LMDZ.COMMON)
    91       call getin_p("ecritphy",ecritphy)
     76  CHARACTER ch1*12
     77  CHARACTER ch80*80
     78
     79  logical chem, h2o
     80
     81  real psurf,pN2 ! added by RW for Gliese 581d N2+CO2
     82
     83  ! initialize constants in comcstfi_mod
     84  rad=prad
     85  cpp=pcpp
     86  g=pg
     87  r=pr
     88  rcp=r/cpp
     89  pi=2.*asin(1.)
     90  avocado = 6.02214179e23   ! added by RW
     91
     92  ! Initialize some "temporal and calendar" related variables
     93  CALL init_time(day_ini,pdaysec,ptimestep)
     94
     95  ! read in 'ecritphy' (frequency of calls to physics, in dynamical steps)
     96  ! (also done in dyn3d/defrun_new but not in LMDZ.COMMON)
     97  call getin_p("ecritphy",ecritphy)
    9298
    9399! --------------------------------------------------------------
     
    95101! --------------------------------------------------------------
    96102     
    97       ! check that 'callphys.def' file is around
    98       OPEN(99,file='callphys.def',status='old',form='formatted'
    99      &     ,iostat=ierr)
    100       CLOSE(99)
    101       IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
     103  ! check that 'callphys.def' file is around
     104  OPEN(99,file='callphys.def',status='old',form='formatted',iostat=ierr)
     105  CLOSE(99)
     106  IF(ierr.EQ.0) iscallphys=.true. !iscallphys initialised as false in callkeys_mod module
    102107     
    103108!!!      IF(ierr.EQ.0) THEN
    104       IF(iscallphys) THEN
    105          PRINT*
    106          PRINT*
    107          PRINT*,'--------------------------------------------'
    108          PRINT*,' inifis: Parametres pour la physique (callphys.def)'
    109          PRINT*,'--------------------------------------------'
    110 
    111          write(*,*) "Directory where external input files are:"
    112          ! default 'datadir' is set in "datadir_mod"
    113          call getin_p("datadir",datadir) ! default path
    114          write(*,*) " datadir = ",trim(datadir)
    115 
    116          write(*,*) "Run with or without tracer transport ?"
    117          tracer=.false. ! default value
    118          call getin_p("tracer",tracer)
    119          write(*,*) " tracer = ",tracer
    120 
    121          write(*,*) "Run with or without atm mass update ",
    122      &      " due to tracer evaporation/condensation?"
    123          mass_redistrib=.false. ! default value
    124          call getin_p("mass_redistrib",mass_redistrib)
    125          write(*,*) " mass_redistrib = ",mass_redistrib
    126 
    127          write(*,*) "Diurnal cycle ?"
    128          write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
    129          diurnal=.true. ! default value
    130          call getin_p("diurnal",diurnal)
    131          write(*,*) " diurnal = ",diurnal
    132 
    133          write(*,*) "Seasonal cycle ?"
    134          write(*,*) "(if season=false, Ls stays constant, to value ",
    135      &   "set in 'start'"
    136          season=.true. ! default value
    137          call getin_p("season",season)
    138          write(*,*) " season = ",season
    139 
    140          write(*,*) "Tidally resonant rotation ?"
    141          tlocked=.false. ! default value
    142          call getin_p("tlocked",tlocked)
    143          write(*,*) "tlocked = ",tlocked
    144 
    145          write(*,*) "Saturn ring shadowing ?"
    146          rings_shadow = .false.
    147          call getin_p("rings_shadow", rings_shadow)
    148          write(*,*) "rings_shadow = ", rings_shadow
     109  IF(iscallphys) THEN
     110     PRINT*
     111     PRINT*
     112     PRINT*,'--------------------------------------------'
     113     PRINT*,' inifis: Parametres pour la physique (callphys.def)'
     114     PRINT*,'--------------------------------------------'
     115
     116     write(*,*) "Directory where external input files are:"
     117     ! default 'datadir' is set in "datadir_mod"
     118     call getin_p("datadir",datadir) ! default path
     119     write(*,*) " datadir = ",trim(datadir)
     120
     121     write(*,*) "Run with or without tracer transport ?"
     122     tracer=.false. ! default value
     123     call getin_p("tracer",tracer)
     124     write(*,*) " tracer = ",tracer
     125
     126     write(*,*) "Run with or without atm mass update ", &
     127            " due to tracer evaporation/condensation?"
     128     mass_redistrib=.false. ! default value
     129     call getin_p("mass_redistrib",mass_redistrib)
     130     write(*,*) " mass_redistrib = ",mass_redistrib
     131
     132     write(*,*) "Diurnal cycle ?"
     133     write(*,*) "(if diurnal=false, diurnal averaged solar heating)"
     134     diurnal=.true. ! default value
     135     call getin_p("diurnal",diurnal)
     136     write(*,*) " diurnal = ",diurnal
     137
     138     write(*,*) "Seasonal cycle ?"
     139     write(*,*) "(if season=false, Ls stays constant, to value ", &
     140         "set in 'start'"
     141     season=.true. ! default value
     142     call getin_p("season",season)
     143     write(*,*) " season = ",season
     144
     145     write(*,*) "Tidally resonant rotation ?"
     146     tlocked=.false. ! default value
     147     call getin_p("tlocked",tlocked)
     148     write(*,*) "tlocked = ",tlocked
     149
     150     write(*,*) "Saturn ring shadowing ?"
     151     rings_shadow = .false.
     152     call getin_p("rings_shadow", rings_shadow)
     153     write(*,*) "rings_shadow = ", rings_shadow
    149154         
    150          write(*,*) "Compute latitude-dependent gravity field?"
    151          oblate = .false.
    152          call getin_p("oblate", oblate)
    153          write(*,*) "oblate = ", oblate
    154 
    155          write(*,*) "Flattening of the planet (a-b)/a "
    156          flatten = 0.0
    157          call getin_p("flatten", flatten)
    158          write(*,*) "flatten = ", flatten
     155     write(*,*) "Compute latitude-dependent gravity field?"
     156     oblate = .false.
     157     call getin_p("oblate", oblate)
     158     write(*,*) "oblate = ", oblate
     159
     160     write(*,*) "Flattening of the planet (a-b)/a "
     161     flatten = 0.0
     162     call getin_p("flatten", flatten)
     163     write(*,*) "flatten = ", flatten
    159164         
    160165
    161          write(*,*) "Needed if oblate=.true.: J2"
    162          J2 = 0.0
    163          call getin_p("J2", J2)
    164          write(*,*) "J2 = ", J2
     166     write(*,*) "Needed if oblate=.true.: J2"
     167     J2 = 0.0
     168     call getin_p("J2", J2)
     169     write(*,*) "J2 = ", J2
    165170         
    166          write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
    167          MassPlanet = 0.0
    168          call getin_p("MassPlanet", MassPlanet)
    169          write(*,*) "MassPlanet = ", MassPlanet         
    170 
    171          write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
    172          Rmean = 0.0
    173          call getin_p("Rmean", Rmean)
    174          write(*,*) "Rmean = ", Rmean
     171     write(*,*) "Needed if oblate=.true.: Planet mass (*1e24 kg)"
     172     MassPlanet = 0.0
     173     call getin_p("MassPlanet", MassPlanet)
     174     write(*,*) "MassPlanet = ", MassPlanet         
     175
     176     write(*,*) "Needed if oblate=.true.: Planet mean radius (m)"
     177     Rmean = 0.0
     178     call getin_p("Rmean", Rmean)
     179     write(*,*) "Rmean = ", Rmean
    175180         
    176181! Test of incompatibility:
    177182! if tlocked, then diurnal should be false
    178          if (tlocked.and.diurnal) then
    179            print*,'If diurnal=true, we should turn off tlocked.'
    180            stop
    181          endif
    182 
    183          write(*,*) "Tidal resonance ratio ?"
    184          nres=0          ! default value
    185          call getin_p("nres",nres)
    186          write(*,*) "nres = ",nres
    187 
    188          write(*,*) "Write some extra output to the screen ?"
    189          lwrite=.false. ! default value
    190          call getin_p("lwrite",lwrite)
    191          write(*,*) " lwrite = ",lwrite
    192 
    193          write(*,*) "Save statistics in file stats.nc ?"
    194          callstats=.true. ! default value
    195          call getin_p("callstats",callstats)
    196          write(*,*) " callstats = ",callstats
    197 
    198          write(*,*) "Test energy conservation of model physics ?"
    199          enertest=.false. ! default value
    200          call getin_p("enertest",enertest)
    201          write(*,*) " enertest = ",enertest
    202 
    203          write(*,*) "Check to see if cpp values used match gases.def ?"
    204          check_cpp_match=.true. ! default value
    205          call getin_p("check_cpp_match",check_cpp_match)
    206          write(*,*) " check_cpp_match = ",check_cpp_match
    207 
    208          write(*,*) "call radiative transfer ?"
    209          callrad=.true. ! default value
    210          call getin_p("callrad",callrad)
    211          write(*,*) " callrad = ",callrad
    212 
    213          write(*,*) "call correlated-k radiative transfer ?"
    214          corrk=.true. ! default value
    215          call getin_p("corrk",corrk)
    216          write(*,*) " corrk = ",corrk
    217 
    218          write(*,*) "prohibit calculations outside corrk T grid?"
    219          strictboundcorrk=.true. ! default value
    220          call getin_p("strictboundcorrk",strictboundcorrk)
    221          write(*,*) "strictboundcorrk = ",strictboundcorrk
    222 
    223          write(*,*) "call gaseous absorption in the visible bands?",
    224      &              "(matters only if callrad=T)"
    225          callgasvis=.false. ! default value
    226          call getin_p("callgasvis",callgasvis)
    227          write(*,*) " callgasvis = ",callgasvis
     183     if (tlocked.and.diurnal) then
     184       print*,'If diurnal=true, we should turn off tlocked.'
     185       stop
     186     endif
     187
     188     write(*,*) "Tidal resonance ratio ?"
     189     nres=0          ! default value
     190     call getin_p("nres",nres)
     191     write(*,*) "nres = ",nres
     192
     193     write(*,*) "Write some extra output to the screen ?"
     194     lwrite=.false. ! default value
     195     call getin_p("lwrite",lwrite)
     196     write(*,*) " lwrite = ",lwrite
     197
     198     write(*,*) "Save statistics in file stats.nc ?"
     199     callstats=.true. ! default value
     200     call getin_p("callstats",callstats)
     201     write(*,*) " callstats = ",callstats
     202
     203     write(*,*) "Test energy conservation of model physics ?"
     204     enertest=.false. ! default value
     205     call getin_p("enertest",enertest)
     206     write(*,*) " enertest = ",enertest
     207
     208     write(*,*) "Check to see if cpp values used match gases.def ?"
     209     check_cpp_match=.true. ! default value
     210     call getin_p("check_cpp_match",check_cpp_match)
     211     write(*,*) " check_cpp_match = ",check_cpp_match
     212
     213     write(*,*) "call radiative transfer ?"
     214     callrad=.true. ! default value
     215     call getin_p("callrad",callrad)
     216     write(*,*) " callrad = ",callrad
     217
     218     write(*,*) "call correlated-k radiative transfer ?"
     219     corrk=.true. ! default value
     220     call getin_p("corrk",corrk)
     221     write(*,*) " corrk = ",corrk
     222
     223     write(*,*) "prohibit calculations outside corrk T grid?"
     224     strictboundcorrk=.true. ! default value
     225     call getin_p("strictboundcorrk",strictboundcorrk)
     226     write(*,*) "strictboundcorrk = ",strictboundcorrk
     227
     228     write(*,*) "call gaseous absorption in the visible bands?", &
     229                    "(matters only if callrad=T)"
     230     callgasvis=.false. ! default value
     231     call getin_p("callgasvis",callgasvis)
     232     write(*,*) " callgasvis = ",callgasvis
    228233       
    229          write(*,*) "call continuum opacities in radiative transfer ?",
    230      &              "(matters only if callrad=T)"
    231          continuum=.true. ! default value
    232          call getin_p("continuum",continuum)
    233          write(*,*) " continuum = ",continuum
    234 
    235          write(*,*) "use analytic function for H2O continuum ?"
    236          H2Ocont_simple=.false. ! default value
    237          call getin_p("H2Ocont_simple",H2Ocont_simple)
    238          write(*,*) " H2Ocont_simple = ",H2Ocont_simple
     234     write(*,*) "call continuum opacities in radiative transfer ?", &
     235                    "(matters only if callrad=T)"
     236     continuum=.true. ! default value
     237     call getin_p("continuum",continuum)
     238     write(*,*) " continuum = ",continuum
     239
     240     write(*,*) "use analytic function for H2O continuum ?"
     241     H2Ocont_simple=.false. ! default value
     242     call getin_p("H2Ocont_simple",H2Ocont_simple)
     243     write(*,*) " H2Ocont_simple = ",H2Ocont_simple
    239244 
    240          write(*,*) "call turbulent vertical diffusion ?"
    241          calldifv=.true. ! default value
    242          call getin_p("calldifv",calldifv)
    243          write(*,*) " calldifv = ",calldifv
    244 
    245          write(*,*) "use turbdiff instead of vdifc ?"
    246          UseTurbDiff=.true. ! default value
    247          call getin_p("UseTurbDiff",UseTurbDiff)
    248          write(*,*) " UseTurbDiff = ",UseTurbDiff
    249 
    250          write(*,*) "call convective adjustment ?"
    251          calladj=.true. ! default value
    252          call getin_p("calladj",calladj)
    253          write(*,*) " calladj = ",calladj
    254 
    255          write(*,*) "call CO2 condensation ?"
    256          co2cond=.false. ! default value
    257          call getin_p("co2cond",co2cond)
    258          write(*,*) " co2cond = ",co2cond
     245     write(*,*) "call turbulent vertical diffusion ?"
     246     calldifv=.true. ! default value
     247     call getin_p("calldifv",calldifv)
     248     write(*,*) " calldifv = ",calldifv
     249
     250     write(*,*) "use turbdiff instead of vdifc ?"
     251     UseTurbDiff=.true. ! default value
     252     call getin_p("UseTurbDiff",UseTurbDiff)
     253     write(*,*) " UseTurbDiff = ",UseTurbDiff
     254
     255     write(*,*) "call convective adjustment ?"
     256     calladj=.true. ! default value
     257     call getin_p("calladj",calladj)
     258     write(*,*) " calladj = ",calladj
     259
     260     write(*,*) "call CO2 condensation ?"
     261     co2cond=.false. ! default value
     262     call getin_p("co2cond",co2cond)
     263     write(*,*) " co2cond = ",co2cond
    259264! Test of incompatibility
    260          if (co2cond.and.(.not.tracer)) then
    261             print*,'We need a CO2 ice tracer to condense CO2'
    262             call abort
    263          endif
     265     if (co2cond.and.(.not.tracer)) then
     266        print*,'We need a CO2 ice tracer to condense CO2'
     267        call abort
     268     endif
    264269 
    265          write(*,*) "CO2 supersaturation level ?"
    266          co2supsat=1.0 ! default value
    267          call getin_p("co2supsat",co2supsat)
    268          write(*,*) " co2supsat = ",co2supsat
    269 
    270          write(*,*) "Radiative timescale for Newtonian cooling ?"
    271          tau_relax=30. ! default value
    272          call getin_p("tau_relax",tau_relax)
    273          write(*,*) " tau_relax = ",tau_relax
    274          tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
    275 
    276          write(*,*)"call thermal conduction in the soil ?"
    277          callsoil=.true. ! default value
    278          call getin_p("callsoil",callsoil)
    279          write(*,*) " callsoil = ",callsoil
     270     write(*,*) "CO2 supersaturation level ?"
     271     co2supsat=1.0 ! default value
     272     call getin_p("co2supsat",co2supsat)
     273     write(*,*) " co2supsat = ",co2supsat
     274
     275     write(*,*) "Radiative timescale for Newtonian cooling ?"
     276     tau_relax=30. ! default value
     277     call getin_p("tau_relax",tau_relax)
     278     write(*,*) " tau_relax = ",tau_relax
     279     tau_relax=tau_relax*24*3600 ! convert Earth days --> seconds
     280
     281     write(*,*)"call thermal conduction in the soil ?"
     282     callsoil=.true. ! default value
     283     call getin_p("callsoil",callsoil)
     284     write(*,*) " callsoil = ",callsoil
    280285         
    281          write(*,*)"Rad transfer is computed every iradia",
    282      &             " physical timestep"
    283          iradia=1 ! default value
    284          call getin_p("iradia",iradia)
    285          write(*,*)" iradia = ",iradia
     286     write(*,*)"Rad transfer is computed every iradia", &
     287                   " physical timestep"
     288     iradia=1 ! default value
     289     call getin_p("iradia",iradia)
     290     write(*,*)" iradia = ",iradia
    286291       
    287          write(*,*)"Rayleigh scattering ?"
    288          rayleigh=.false.
    289          call getin_p("rayleigh",rayleigh)
    290          write(*,*)" rayleigh = ",rayleigh
    291 
    292          write(*,*) "Use blackbody for stellar spectrum ?"
    293          stelbbody=.false. ! default value
    294          call getin_p("stelbbody",stelbbody)
    295          write(*,*) " stelbbody = ",stelbbody
    296 
    297          write(*,*) "Stellar blackbody temperature ?"
    298          stelTbb=5800.0 ! default value
    299          call getin_p("stelTbb",stelTbb)
    300          write(*,*) " stelTbb = ",stelTbb
    301 
    302          write(*,*)"Output mean OLR in 1D?"
    303          meanOLR=.false.
    304          call getin_p("meanOLR",meanOLR)
    305          write(*,*)" meanOLR = ",meanOLR
    306 
    307          write(*,*)"Output spectral OLR in 3D?"
    308          specOLR=.false.
    309          call getin_p("specOLR",specOLR)
    310          write(*,*)" specOLR = ",specOLR
    311 
    312          write(*,*)"Operate in kastprof mode?"
    313          kastprof=.false.
    314          call getin_p("kastprof",kastprof)
    315          write(*,*)" kastprof = ",kastprof
    316 
    317          write(*,*)"Uniform absorption in radiative transfer?"
    318          graybody=.false.
    319          call getin_p("graybody",graybody)
    320          write(*,*)" graybody = ",graybody
     292     write(*,*)"Rayleigh scattering ?"
     293     rayleigh=.false.
     294     call getin_p("rayleigh",rayleigh)
     295     write(*,*)" rayleigh = ",rayleigh
     296
     297     write(*,*) "Use blackbody for stellar spectrum ?"
     298     stelbbody=.false. ! default value
     299     call getin_p("stelbbody",stelbbody)
     300     write(*,*) " stelbbody = ",stelbbody
     301
     302     write(*,*) "Stellar blackbody temperature ?"
     303     stelTbb=5800.0 ! default value
     304     call getin_p("stelTbb",stelTbb)
     305     write(*,*) " stelTbb = ",stelTbb
     306
     307     write(*,*)"Output mean OLR in 1D?"
     308     meanOLR=.false.
     309     call getin_p("meanOLR",meanOLR)
     310     write(*,*)" meanOLR = ",meanOLR
     311
     312     write(*,*)"Output spectral OLR in 3D?"
     313     specOLR=.false.
     314     call getin_p("specOLR",specOLR)
     315     write(*,*)" specOLR = ",specOLR
     316
     317     write(*,*)"Operate in kastprof mode?"
     318     kastprof=.false.
     319     call getin_p("kastprof",kastprof)
     320     write(*,*)" kastprof = ",kastprof
     321
     322     write(*,*)"Uniform absorption in radiative transfer?"
     323     graybody=.false.
     324     call getin_p("graybody",graybody)
     325     write(*,*)" graybody = ",graybody
    321326
    322327! Slab Ocean
    323          write(*,*) "Use slab-ocean ?"
    324          ok_slab_ocean=.false.         ! default value
    325          call getin_p("ok_slab_ocean",ok_slab_ocean)
    326          write(*,*) "ok_slab_ocean = ",ok_slab_ocean
    327 
    328          write(*,*) "Use slab-sea-ice ?"
    329          ok_slab_sic=.true.         ! default value
    330          call getin_p("ok_slab_sic",ok_slab_sic)
    331          write(*,*) "ok_slab_sic = ",ok_slab_sic
    332 
    333          write(*,*) "Use heat transport for the ocean ?"
    334          ok_slab_heat_transp=.true.   ! default value
    335          call getin_p("ok_slab_heat_transp",ok_slab_heat_transp)
    336          write(*,*) "ok_slab_heat_transp = ",ok_slab_heat_transp
     328     write(*,*) "Use slab-ocean ?"
     329     ok_slab_ocean=.false.         ! default value
     330     call getin_p("ok_slab_ocean",ok_slab_ocean)
     331     write(*,*) "ok_slab_ocean = ",ok_slab_ocean
     332
     333     write(*,*) "Use slab-sea-ice ?"
     334     ok_slab_sic=.true.         ! default value
     335     call getin_p("ok_slab_sic",ok_slab_sic)
     336     write(*,*) "ok_slab_sic = ",ok_slab_sic
     337
     338     write(*,*) "Use heat transport for the ocean ?"
     339     ok_slab_heat_transp=.true.   ! default value
     340     call getin_p("ok_slab_heat_transp",ok_slab_heat_transp)
     341     write(*,*) "ok_slab_heat_transp = ",ok_slab_heat_transp
    337342
    338343
     
    340345! Test of incompatibility:
    341346! if kastprof used, we must be in 1D
    342          if (kastprof.and.(ngrid.gt.1)) then
    343            print*,'kastprof can only be used in 1D!'
    344            call abort
    345          endif
    346 
    347          write(*,*)"Stratospheric temperature for kastprof mode?"
    348          Tstrat=167.0
    349          call getin_p("Tstrat",Tstrat)
    350          write(*,*)" Tstrat = ",Tstrat
    351 
    352          write(*,*)"Remove lower boundary?"
    353          nosurf=.false.
    354          call getin_p("nosurf",nosurf)
    355          write(*,*)" nosurf = ",nosurf
     347     if (kastprof.and.(ngrid.gt.1)) then
     348       print*,'kastprof can only be used in 1D!'
     349       call abort
     350     endif
     351
     352     write(*,*)"Stratospheric temperature for kastprof mode?"
     353     Tstrat=167.0
     354     call getin_p("Tstrat",Tstrat)
     355     write(*,*)" Tstrat = ",Tstrat
     356
     357     write(*,*)"Remove lower boundary?"
     358     nosurf=.false.
     359     call getin_p("nosurf",nosurf)
     360     write(*,*)" nosurf = ",nosurf
    356361
    357362! Tests of incompatibility:
    358          if (nosurf.and.callsoil) then
    359            print*,'nosurf not compatible with soil scheme!'
    360            print*,'... got to make a choice!'
    361            call abort
    362          endif
    363 
    364          write(*,*)"Add an internal heat flux?",
    365      .             "... matters only if callsoil=F"
    366          intheat=0.
    367          call getin_p("intheat",intheat)
    368          write(*,*)" intheat = ",intheat
    369 
    370          write(*,*)"Use Newtonian cooling for radiative transfer?"
    371          newtonian=.false.
    372          call getin_p("newtonian",newtonian)
    373          write(*,*)" newtonian = ",newtonian
     363     if (nosurf.and.callsoil) then
     364       print*,'nosurf not compatible with soil scheme!'
     365       print*,'... got to make a choice!'
     366       call abort
     367     endif
     368
     369     write(*,*)"Add an internal heat flux?", &
     370                   "... matters only if callsoil=F"
     371     intheat=0.
     372     call getin_p("intheat",intheat)
     373     write(*,*)" intheat = ",intheat
     374
     375     write(*,*)"Use Newtonian cooling for radiative transfer?"
     376     newtonian=.false.
     377     call getin_p("newtonian",newtonian)
     378     write(*,*)" newtonian = ",newtonian
    374379
    375380! Tests of incompatibility:
    376          if (newtonian.and.corrk) then
    377            print*,'newtonian not compatible with correlated-k!'
    378            call abort
    379          endif
    380          if (newtonian.and.calladj) then
    381            print*,'newtonian not compatible with adjustment!'
    382            call abort
    383          endif
    384          if (newtonian.and.calldifv) then
    385            print*,'newtonian not compatible with a boundary layer!'
    386            call abort
    387          endif
    388 
    389          write(*,*)"Test physics timescale in 1D?"
    390          testradtimes=.false.
    391          call getin_p("testradtimes",testradtimes)
    392          write(*,*)" testradtimes = ",testradtimes
     381     if (newtonian.and.corrk) then
     382       print*,'newtonian not compatible with correlated-k!'
     383       call abort
     384     endif
     385     if (newtonian.and.calladj) then
     386       print*,'newtonian not compatible with adjustment!'
     387       call abort
     388     endif
     389     if (newtonian.and.calldifv) then
     390       print*,'newtonian not compatible with a boundary layer!'
     391       call abort
     392     endif
     393
     394     write(*,*)"Test physics timescale in 1D?"
     395     testradtimes=.false.
     396     call getin_p("testradtimes",testradtimes)
     397     write(*,*)" testradtimes = ",testradtimes
    393398
    394399! Test of incompatibility:
    395400! if testradtimes used, we must be in 1D
    396          if (testradtimes.and.(ngrid.gt.1)) then
    397            print*,'testradtimes can only be used in 1D!'
    398            call abort
    399          endif
    400 
    401          write(*,*)"Default planetary temperature?"
    402          tplanet=215.0
    403          call getin_p("tplanet",tplanet)
    404          write(*,*)" tplanet = ",tplanet
    405 
    406          write(*,*)"Which star?"
    407          startype=1 ! default value = Sol
    408          call getin_p("startype",startype)
    409          write(*,*)" startype = ",startype
    410 
    411          write(*,*)"Value of stellar flux at 1 AU?"
    412          Fat1AU=1356.0 ! default value = Sol today
    413          call getin_p("Fat1AU",Fat1AU)
    414          write(*,*)" Fat1AU = ",Fat1AU
     401     if (testradtimes.and.(ngrid.gt.1)) then
     402       print*,'testradtimes can only be used in 1D!'
     403       call abort
     404     endif
     405
     406     write(*,*)"Default planetary temperature?"
     407     tplanet=215.0
     408     call getin_p("tplanet",tplanet)
     409     write(*,*)" tplanet = ",tplanet
     410
     411     write(*,*)"Which star?"
     412     startype=1 ! default value = Sol
     413     call getin_p("startype",startype)
     414     write(*,*)" startype = ",startype
     415
     416     write(*,*)"Value of stellar flux at 1 AU?"
     417     Fat1AU=1356.0 ! default value = Sol today
     418     call getin_p("Fat1AU",Fat1AU)
     419     write(*,*)" Fat1AU = ",Fat1AU
    415420
    416421
    417422! TRACERS:
    418423
    419          write(*,*)"Varying H2O cloud fraction?"
    420          CLFvarying=.false.     ! default value
    421          call getin_p("CLFvarying",CLFvarying)
    422          write(*,*)" CLFvarying = ",CLFvarying
    423 
    424          write(*,*)"Value of fixed H2O cloud fraction?"
    425          CLFfixval=1.0                ! default value
    426          call getin_p("CLFfixval",CLFfixval)
    427          write(*,*)" CLFfixval = ",CLFfixval
    428 
    429          write(*,*)"fixed radii for Cloud particles?"
    430          radfixed=.false. ! default value
    431          call getin_p("radfixed",radfixed)
    432          write(*,*)" radfixed = ",radfixed
    433 
    434          if(kastprof)then
    435             radfixed=.true.
    436          endif 
    437 
    438         write(*,*)"Number mixing ratio of CO2 ice particles:"
    439          Nmix_co2=1.e6 ! default value
    440          call getin_p("Nmix_co2",Nmix_co2)
    441          write(*,*)" Nmix_co2 = ",Nmix_co2
     424     write(*,*)"Varying H2O cloud fraction?"
     425     CLFvarying=.false.     ! default value
     426     call getin_p("CLFvarying",CLFvarying)
     427     write(*,*)" CLFvarying = ",CLFvarying
     428
     429     write(*,*)"Value of fixed H2O cloud fraction?"
     430     CLFfixval=1.0                ! default value
     431     call getin_p("CLFfixval",CLFfixval)
     432     write(*,*)" CLFfixval = ",CLFfixval
     433
     434     write(*,*)"fixed radii for Cloud particles?"
     435     radfixed=.false. ! default value
     436     call getin_p("radfixed",radfixed)
     437     write(*,*)" radfixed = ",radfixed
     438
     439     if(kastprof)then
     440        radfixed=.true.
     441     endif 
     442
     443    write(*,*)"Number mixing ratio of CO2 ice particles:"
     444     Nmix_co2=1.e6 ! default value
     445     call getin_p("Nmix_co2",Nmix_co2)
     446     write(*,*)" Nmix_co2 = ",Nmix_co2
    442447
    443448!         write(*,*)"Number of radiatively active aerosols:"
     
    446451!         write(*,*)" naerkind = ",naerkind
    447452
    448          write(*,*)"Opacity of dust (if used):"
    449          dusttau=0. ! default value
    450          call getin_p("dusttau",dusttau)
    451          write(*,*)" dusttau = ",dusttau
    452 
    453          write(*,*)"Radiatively active CO2 aerosols?"
    454          aeroco2=.false.     ! default value
    455          call getin_p("aeroco2",aeroco2)
    456          write(*,*)" aeroco2 = ",aeroco2
    457 
    458          write(*,*)"Fixed CO2 aerosol distribution?"
    459          aerofixco2=.false.     ! default value
    460          call getin_p("aerofixco2",aerofixco2)
    461          write(*,*)" aerofixco2 = ",aerofixco2
    462 
    463          write(*,*)"Radiatively active water ice?"
    464          aeroh2o=.false.     ! default value
    465          call getin_p("aeroh2o",aeroh2o)
    466          write(*,*)" aeroh2o = ",aeroh2o
    467 
    468          write(*,*)"Fixed H2O aerosol distribution?"
    469          aerofixh2o=.false.     ! default value
    470          call getin_p("aerofixh2o",aerofixh2o)
    471          write(*,*)" aerofixh2o = ",aerofixh2o
    472 
    473          write(*,*)"Radiatively active sulfuric acid aersols?"
    474          aeroh2so4=.false.     ! default value
    475          call getin_p("aeroh2so4",aeroh2so4)
    476          write(*,*)" aeroh2so4 = ",aeroh2so4
     453     write(*,*)"Opacity of dust (if used):"
     454     dusttau=0. ! default value
     455     call getin_p("dusttau",dusttau)
     456     write(*,*)" dusttau = ",dusttau
     457
     458     write(*,*)"Radiatively active CO2 aerosols?"
     459     aeroco2=.false.     ! default value
     460     call getin_p("aeroco2",aeroco2)
     461     write(*,*)" aeroco2 = ",aeroco2
     462
     463     write(*,*)"Fixed CO2 aerosol distribution?"
     464     aerofixco2=.false.     ! default value
     465     call getin_p("aerofixco2",aerofixco2)
     466     write(*,*)" aerofixco2 = ",aerofixco2
     467
     468     write(*,*)"Radiatively active water ice?"
     469     aeroh2o=.false.     ! default value
     470     call getin_p("aeroh2o",aeroh2o)
     471     write(*,*)" aeroh2o = ",aeroh2o
     472
     473     write(*,*)"Fixed H2O aerosol distribution?"
     474     aerofixh2o=.false.     ! default value
     475     call getin_p("aerofixh2o",aerofixh2o)
     476     write(*,*)" aerofixh2o = ",aerofixh2o
     477
     478     write(*,*)"Radiatively active sulfuric acid aersols?"
     479     aeroh2so4=.false.     ! default value
     480     call getin_p("aeroh2so4",aeroh2so4)
     481     write(*,*)" aeroh2so4 = ",aeroh2so4
    477482         
    478483!=================================
    479484
    480         write(*,*)"Radiatively active two-layer aersols?"
    481          aeroback2lay=.false.     ! default value
    482          call getin_p("aeroback2lay",aeroback2lay)
    483          write(*,*)" aeroback2lay = ",aeroback2lay
    484 
    485          write(*,*)"TWOLAY AEROSOL: total optical depth ",
    486      &              "in the tropospheric layer (visible)"
    487          obs_tau_col_tropo=8.D0
    488          call getin_p("obs_tau_col_tropo",obs_tau_col_tropo)
    489          write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo
    490 
    491          write(*,*)"TWOLAY AEROSOL: total optical depth ",
    492      &              "in the stratospheric layer (visible)"
    493          obs_tau_col_strato=0.08D0
    494          call getin_p("obs_tau_col_strato",obs_tau_col_strato)
    495          write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato
    496 
    497          write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa"
    498          pres_bottom_tropo=66000.0
    499          call getin_p("pres_bottom_tropo",pres_bottom_tropo)
    500          write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo
    501 
    502          write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa"
    503          pres_top_tropo=18000.0
    504          call getin_p("pres_top_tropo",pres_top_tropo)
    505          write(*,*)" pres_top_tropo = ",pres_top_tropo
    506 
    507          write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa"
    508          pres_bottom_strato=2000.0
    509          call getin_p("pres_bottom_strato",pres_bottom_strato)
    510          write(*,*)" pres_bottom_strato = ",pres_bottom_strato
    511 
    512          write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa"
    513          pres_top_strato=100.0
    514          call getin_p("pres_top_strato",pres_top_strato)
    515          write(*,*)" pres_top_strato = ",pres_top_strato
    516 
    517          write(*,*)"TWOLAY AEROSOL: particle size in the ",
    518      &              "tropospheric layer, in meters"
    519          size_tropo=2.e-6
    520          call getin_p("size_tropo",size_tropo)
    521          write(*,*)" size_tropo = ",size_tropo
    522 
    523          write(*,*)"TWOLAY AEROSOL: particle size in the ",
    524      &              "stratospheric layer, in meters"
    525          size_strato=1.e-7
    526          call getin_p("size_strato",size_strato)
    527          write(*,*)" size_strato = ",size_strato
     485    write(*,*)"Radiatively active two-layer aersols?"
     486     aeroback2lay=.false.     ! default value
     487     call getin_p("aeroback2lay",aeroback2lay)
     488     write(*,*)" aeroback2lay = ",aeroback2lay
     489
     490     write(*,*)"TWOLAY AEROSOL: total optical depth ", &
     491                    "in the tropospheric layer (visible)"
     492     obs_tau_col_tropo=8.D0
     493     call getin_p("obs_tau_col_tropo",obs_tau_col_tropo)
     494     write(*,*)" obs_tau_col_tropo = ",obs_tau_col_tropo
     495
     496     write(*,*)"TWOLAY AEROSOL: total optical depth ", &
     497                    "in the stratospheric layer (visible)"
     498     obs_tau_col_strato=0.08D0
     499     call getin_p("obs_tau_col_strato",obs_tau_col_strato)
     500     write(*,*)" obs_tau_col_strato = ",obs_tau_col_strato
     501
     502     write(*,*)"TWOLAY AEROSOL: pres_bottom_tropo? in pa"
     503     pres_bottom_tropo=66000.0
     504     call getin_p("pres_bottom_tropo",pres_bottom_tropo)
     505     write(*,*)" pres_bottom_tropo = ",pres_bottom_tropo
     506
     507     write(*,*)"TWOLAY AEROSOL: pres_top_tropo? in pa"
     508     pres_top_tropo=18000.0
     509     call getin_p("pres_top_tropo",pres_top_tropo)
     510     write(*,*)" pres_top_tropo = ",pres_top_tropo
     511
     512     write(*,*)"TWOLAY AEROSOL: pres_bottom_strato? in pa"
     513     pres_bottom_strato=2000.0
     514     call getin_p("pres_bottom_strato",pres_bottom_strato)
     515     write(*,*)" pres_bottom_strato = ",pres_bottom_strato
     516
     517     write(*,*)"TWOLAY AEROSOL: pres_top_strato? in pa"
     518     pres_top_strato=100.0
     519     call getin_p("pres_top_strato",pres_top_strato)
     520     write(*,*)" pres_top_strato = ",pres_top_strato
     521
     522     write(*,*)"TWOLAY AEROSOL: particle size in the ", &
     523                    "tropospheric layer, in meters"
     524     size_tropo=2.e-6
     525     call getin_p("size_tropo",size_tropo)
     526     write(*,*)" size_tropo = ",size_tropo
     527
     528     write(*,*)"TWOLAY AEROSOL: particle size in the ", &
     529                    "stratospheric layer, in meters"
     530     size_strato=1.e-7
     531     call getin_p("size_strato",size_strato)
     532     write(*,*)" size_strato = ",size_strato
    528533
    529534!=================================
    530535
    531          write(*,*)"Cloud pressure level (with kastprof only):"
    532          cloudlvl=0. ! default value
    533          call getin_p("cloudlvl",cloudlvl)
    534          write(*,*)" cloudlvl = ",cloudlvl
    535 
    536          write(*,*)"Is the variable gas species radiatively active?"
    537          Tstrat=167.0
    538          varactive=.false.
    539          call getin_p("varactive",varactive)
    540          write(*,*)" varactive = ",varactive
    541 
    542          write(*,*)"Is the variable gas species distribution set?"
    543          varfixed=.false.
    544          call getin_p("varfixed",varfixed)
    545          write(*,*)" varfixed = ",varfixed
    546 
    547          write(*,*)"What is the saturation % of the variable species?"
    548          satval=0.8
    549          call getin_p("satval",satval)
    550          write(*,*)" satval = ",satval
     536     write(*,*)"Cloud pressure level (with kastprof only):"
     537     cloudlvl=0. ! default value
     538     call getin_p("cloudlvl",cloudlvl)
     539     write(*,*)" cloudlvl = ",cloudlvl
     540
     541     write(*,*)"Is the variable gas species radiatively active?"
     542     Tstrat=167.0
     543     varactive=.false.
     544     call getin_p("varactive",varactive)
     545     write(*,*)" varactive = ",varactive
     546
     547     write(*,*)"Is the variable gas species distribution set?"
     548     varfixed=.false.
     549     call getin_p("varfixed",varfixed)
     550     write(*,*)" varfixed = ",varfixed
     551
     552     write(*,*)"What is the saturation % of the variable species?"
     553     satval=0.8
     554     call getin_p("satval",satval)
     555     write(*,*)" satval = ",satval
    551556
    552557
    553558! Test of incompatibility:
    554559! if varactive, then varfixed should be false
    555          if (varactive.and.varfixed) then
    556            print*,'if varactive, varfixed must be OFF!'
    557            stop
    558          endif
    559 
    560          write(*,*) "Gravitationnal sedimentation ?"
    561          sedimentation=.false. ! default value
    562          call getin_p("sedimentation",sedimentation)
    563          write(*,*) " sedimentation = ",sedimentation
    564 
    565          write(*,*) "Compute water cycle ?"
    566          water=.false. ! default value
    567          call getin_p("water",water)
    568          write(*,*) " water = ",water
     560     if (varactive.and.varfixed) then
     561       print*,'if varactive, varfixed must be OFF!'
     562       stop
     563     endif
     564
     565     write(*,*) "Gravitationnal sedimentation ?"
     566     sedimentation=.false. ! default value
     567     call getin_p("sedimentation",sedimentation)
     568     write(*,*) " sedimentation = ",sedimentation
     569
     570     write(*,*) "Compute water cycle ?"
     571     water=.false. ! default value
     572     call getin_p("water",water)
     573     write(*,*) " water = ",water
    569574         
    570575! Test of incompatibility:
    571576! if water is true, there should be at least a tracer
    572          if (water.and.(.not.tracer)) then
    573            print*,'if water is ON, tracer must be ON too!'
    574            stop
    575          endif
    576 
    577          write(*,*) "Include water condensation ?"
    578          watercond=.false. ! default value
    579          call getin_p("watercond",watercond)
    580          write(*,*) " watercond = ",watercond
     577     if (water.and.(.not.tracer)) then
     578        print*,'if water is ON, tracer must be ON too!'
     579        stop
     580     endif
     581
     582     write(*,*) "Include water condensation ?"
     583     watercond=.false. ! default value
     584     call getin_p("watercond",watercond)
     585     write(*,*) " watercond = ",watercond
    581586
    582587! Test of incompatibility:
    583588! if watercond is used, then water should be used too
    584          if (watercond.and.(.not.water)) then
    585            print*,'if watercond is used, water should be used too'
    586            stop
    587          endif
    588 
    589          write(*,*) "Include water precipitation ?"
    590          waterrain=.false. ! default value
    591          call getin_p("waterrain",waterrain)
    592          write(*,*) " waterrain = ",waterrain
    593 
    594          write(*,*) "Include surface hydrology ?"
    595          hydrology=.false. ! default value
    596          call getin_p("hydrology",hydrology)
    597          write(*,*) " hydrology = ",hydrology
    598 
    599          write(*,*) "Evolve surface water sources ?"
    600          sourceevol=.false. ! default value
    601          call getin_p("sourceevol",sourceevol)
    602          write(*,*) " sourceevol = ",sourceevol
    603 
    604          write(*,*) "Ice evolution timestep ?"
    605          icetstep=100.0 ! default value
    606          call getin_p("icetstep",icetstep)
    607          write(*,*) " icetstep = ",icetstep
     589     if (watercond.and.(.not.water)) then
     590        print*,'if watercond is used, water should be used too'
     591        stop
     592     endif
     593
     594     write(*,*) "Include water precipitation ?"
     595     waterrain=.false. ! default value
     596     call getin_p("waterrain",waterrain)
     597     write(*,*) " waterrain = ",waterrain
     598
     599     write(*,*) "Include surface hydrology ?"
     600     hydrology=.false. ! default value
     601     call getin_p("hydrology",hydrology)
     602     write(*,*) " hydrology = ",hydrology
     603
     604     write(*,*) "Evolve surface water sources ?"
     605     sourceevol=.false. ! default value
     606     call getin_p("sourceevol",sourceevol)
     607     write(*,*) " sourceevol = ",sourceevol
     608
     609     write(*,*) "Ice evolution timestep ?"
     610     icetstep=100.0 ! default value
     611     call getin_p("icetstep",icetstep)
     612     write(*,*) " icetstep = ",icetstep
    608613         
    609          write(*,*) "Spectral Dependant albedo ?"
    610          albedo_spectral_mode=.false. ! default value
    611          call getin_p("albedo_spectral_mode",albedo_spectral_mode)
    612          write(*,*) " albedo_spectral_mode = ",albedo_spectral_mode
    613 
    614          write(*,*) "Snow albedo ?"
    615          write(*,*) "If albedo_spectral_mode=.true., then this "
    616          write(*,*) "corresponds to the 0.5 microns snow albedo."
    617          albedosnow=0.5         ! default value
    618          call getin_p("albedosnow",albedosnow)
    619          write(*,*) " albedosnow = ",albedosnow
     614     write(*,*) "Spectral Dependant albedo ?"
     615     albedo_spectral_mode=.false. ! default value
     616     call getin_p("albedo_spectral_mode",albedo_spectral_mode)
     617     write(*,*) " albedo_spectral_mode = ",albedo_spectral_mode
     618
     619     write(*,*) "Snow albedo ?"
     620     write(*,*) "If albedo_spectral_mode=.true., then this "
     621     write(*,*) "corresponds to the 0.5 microns snow albedo."
     622     albedosnow=0.5         ! default value
     623     call getin_p("albedosnow",albedosnow)
     624     write(*,*) " albedosnow = ",albedosnow
    620625         
    621          write(*,*) "CO2 ice albedo ?"
    622          albedoco2ice=0.5       ! default value
    623          call getin_p("albedoco2ice",albedoco2ice)
    624          write(*,*) " albedoco2ice = ",albedoco2ice
    625 
    626          write(*,*) "Maximum ice thickness ?"
    627          maxicethick=2.0         ! default value
    628          call getin_p("maxicethick",maxicethick)
    629          write(*,*) " maxicethick = ",maxicethick
    630 
    631          write(*,*) "Freezing point of seawater ?"
    632          Tsaldiff=-1.8          ! default value
    633          call getin_p("Tsaldiff",Tsaldiff)
    634          write(*,*) " Tsaldiff = ",Tsaldiff
    635 
    636          write(*,*) "Does user want to force cpp and mugaz?"
    637          force_cpp=.false. ! default value
    638          call getin_p("force_cpp",force_cpp)
    639          write(*,*) " force_cpp = ",force_cpp
    640 
    641          if (force_cpp) then
    642            mugaz = -99999.
    643            PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
    644            call getin_p("mugaz",mugaz)
    645            IF (mugaz.eq.-99999.) THEN
    646                PRINT *, "mugaz must be set if force_cpp = T"
    647                STOP
    648            ELSE
    649                write(*,*) "mugaz=",mugaz
    650            ENDIF
    651            cpp = -99999.
    652            PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
    653            call getin_p("cpp",cpp)
    654            IF (cpp.eq.-99999.) THEN
    655                PRINT *, "cpp must be set if force_cpp = T"
    656                STOP
    657            ELSE
    658                write(*,*) "cpp=",cpp
    659            ENDIF
     626     write(*,*) "CO2 ice albedo ?"
     627     albedoco2ice=0.5       ! default value
     628     call getin_p("albedoco2ice",albedoco2ice)
     629     write(*,*) " albedoco2ice = ",albedoco2ice
     630
     631     write(*,*) "Maximum ice thickness ?"
     632     maxicethick=2.0         ! default value
     633     call getin_p("maxicethick",maxicethick)
     634     write(*,*) " maxicethick = ",maxicethick
     635
     636     write(*,*) "Freezing point of seawater ?"
     637     Tsaldiff=-1.8          ! default value
     638     call getin_p("Tsaldiff",Tsaldiff)
     639     write(*,*) " Tsaldiff = ",Tsaldiff
     640
     641     write(*,*) "Does user want to force cpp and mugaz?"
     642     force_cpp=.false. ! default value
     643     call getin_p("force_cpp",force_cpp)
     644     write(*,*) " force_cpp = ",force_cpp
     645
     646     if (force_cpp) then
     647       mugaz = -99999.
     648       PRINT *,'MEAN MOLECULAR MASS in g mol-1 ?'
     649       call getin_p("mugaz",mugaz)
     650       IF (mugaz.eq.-99999.) THEN
     651           PRINT *, "mugaz must be set if force_cpp = T"
     652           STOP
     653       ELSE
     654           write(*,*) "mugaz=",mugaz
     655       ENDIF
     656       cpp = -99999.
     657       PRINT *,'SPECIFIC HEAT CAPACITY in J K-1 kg-1 ?'
     658       call getin_p("cpp",cpp)
     659       IF (cpp.eq.-99999.) THEN
     660           PRINT *, "cpp must be set if force_cpp = T"
     661           STOP
     662       ELSE
     663           write(*,*) "cpp=",cpp
     664       ENDIF
    660665!         else
    661666!           mugaz=8.314*1000./pr
    662          endif
    663          call su_gases
    664          call calc_cpp_mugaz
    665 
    666          PRINT*,'--------------------------------------------'
    667          PRINT*
    668          PRINT*
    669       ELSE
    670          write(*,*)
    671          write(*,*) 'Cannot read file callphys.def. Is it here ?'
    672          stop
    673       ENDIF
    674 
    675 8000  FORMAT(t5,a12,l8)
    676 8001  FORMAT(t5,a12,i8)
    677 
    678       PRINT*
    679       PRINT*,'inifis: daysec',daysec
    680       PRINT*
    681       PRINT*,'inifis: The radiative transfer is computed:'
    682       PRINT*,'           each ',iradia,' physical time-step'
    683       PRINT*,'        or each ',iradia*dtphys,' seconds'
    684       PRINT*
     667     endif ! of if (force_cpp)
     668     call su_gases
     669     call calc_cpp_mugaz
     670
     671     PRINT*,'--------------------------------------------'
     672     PRINT*
     673     PRINT*
     674  ELSE
     675     write(*,*)
     676     write(*,*) 'Cannot read file callphys.def. Is it here ?'
     677     stop
     678  ENDIF ! of IF(iscallphys)
     679
     680  PRINT*
     681  PRINT*,'inifis: daysec',daysec
     682  PRINT*
     683  PRINT*,'inifis: The radiative transfer is computed:'
     684  PRINT*,'           each ',iradia,' physical time-step'
     685  PRINT*,'        or each ',iradia*dtphys,' seconds'
     686  PRINT*
    685687
    686688
     
    689691!     ------------------------
    690692
    691       ! ALLOCATE ARRAYS IN comgeomfi_h
    692       IF (.not. ALLOCATED(lati)) ALLOCATE(lati(ngrid))
    693       IF (.not. ALLOCATED(long)) ALLOCATE(long(ngrid))
    694       IF (.not. ALLOCATED(area)) ALLOCATE(area(ngrid))
    695 
    696       CALL SCOPY(ngrid,plon,1,long,1)
    697       CALL SCOPY(ngrid,plat,1,lati,1)
    698       CALL SCOPY(ngrid,parea,1,area,1)
    699       totarea=SSUM(ngrid,area,1)
    700       call planetwide_sumval(area,totarea_planet)
    701 
    702       !! those are defined in comdiurn_h.F90
    703       IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
    704       IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
    705       IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
    706       IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
    707 
    708       DO ig=1,ngrid
    709          sinlat(ig)=sin(plat(ig))
    710          coslat(ig)=cos(plat(ig))
    711          sinlon(ig)=sin(plon(ig))
    712          coslon(ig)=cos(plon(ig))
    713       ENDDO
    714 
    715       pi=2.*asin(1.) ! NB: pi is a common in comcstfi_mod
    716 
    717       ! allocate "comsoil_h" arrays
    718       call ini_comsoil_h(ngrid)
     693  ! ALLOCATE ARRAYS IN comgeomfi_h
     694  IF (.not. ALLOCATED(lati)) ALLOCATE(lati(ngrid))
     695  IF (.not. ALLOCATED(long)) ALLOCATE(long(ngrid))
     696  IF (.not. ALLOCATED(area)) ALLOCATE(area(ngrid))
     697
     698  CALL SCOPY(ngrid,plon,1,long,1)
     699  CALL SCOPY(ngrid,plat,1,lati,1)
     700  CALL SCOPY(ngrid,parea,1,area,1)
     701  totarea=SSUM(ngrid,area,1)
     702  call planetwide_sumval(area,totarea_planet)
     703
     704  !! those are defined in comdiurn_h.F90
     705  IF (.not.ALLOCATED(sinlat)) ALLOCATE(sinlat(ngrid))
     706  IF (.not.ALLOCATED(coslat)) ALLOCATE(coslat(ngrid))
     707  IF (.not.ALLOCATED(sinlon)) ALLOCATE(sinlon(ngrid))
     708  IF (.not.ALLOCATED(coslon)) ALLOCATE(coslon(ngrid))
     709
     710  DO ig=1,ngrid
     711     sinlat(ig)=sin(plat(ig))
     712     coslat(ig)=cos(plat(ig))
     713     sinlon(ig)=sin(plon(ig))
     714     coslon(ig)=cos(plon(ig))
     715  ENDDO
     716
     717  ! allocate "comsoil_h" arrays
     718  call ini_comsoil_h(ngrid)
    719719     
    720       END
     720  END SUBROUTINE inifis
     721
     722END MODULE inifis_mod
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite.F

    r1422 r1524  
    22
    33      use comsoil_h, only: mlayer, nsoilmx
    4       use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, daysec, dtphys,
    5      &                        pi
     4      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, pi
     5      use time_phylmdz_mod, only: daysec, dtphys
    66      USE comvert_mod, ONLY: ap,bp,aps,bps,pseudoalt
    77      USE logic_mod, ONLY: fxyhypb,ysinus
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite_specIR.F

    r1422 r1524  
    33      use radinc_h, only: L_NSPECTI
    44      use radcommon_h, only: WNOI,DWNI
    5       use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, daysec, dtphys,
    6      &                        pi
     5      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, pi
     6      use time_phylmdz_mod, only: daysec, dtphys
    77      USE logic_mod, ONLY: fxyhypb,ysinus
    88      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
  • trunk/LMDZ.GENERIC/libf/phystd/iniwrite_specVI.F

    r1422 r1524  
    44      use radcommon_h, only: WNOV,DWNV
    55      use comsoil_h
    6       use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, daysec, dtphys,
    7      &                        pi
     6      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, pi
     7      use time_phylmdz_mod, only: daysec, dtphys
    88      USE logic_mod, ONLY: fxyhypb,ysinus
    99      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
  • trunk/LMDZ.GENERIC/libf/phystd/phyredem.F90

    r1482 r1524  
    1919  use planete_mod, only: year_day, periastr, apoastr, peri_day, &
    2020                         obliquit, z0, lmixmin, emin_turb
    21   use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, daysec
     21  use comcstfi_mod, only: rad, omeg, g, mugaz, rcp
     22  use time_phylmdz_mod, only: daysec
    2223
    2324  implicit none
  • trunk/LMDZ.GENERIC/libf/phystd/physiq.F90

    r1498 r1524  
    3434      use planete_mod, only: apoastr, periastr, year_day, peri_day, &
    3535                            obliquit, nres, z0
    36       use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp, daysec
     36      use comcstfi_mod, only: pi, g, rcp, r, rad, mugaz, cpp
     37      use time_phylmdz_mod, only: daysec
    3738      use callkeys_mod
    3839      implicit none
     
    127128!     Authors
    128129!     -------
    129 !           Frederic Hourdin    15/10/93
    130 !           Francois Forget     1994
    131 !           Christophe Hourdin  02/1997
     130!           Frederic Hourdin        15/10/93
     131!           Francois Forget        1994
     132!           Christophe Hourdin        02/1997
    132133!           Subroutine completely rewritten by F. Forget (01/2000)
    133134!           Water ice clouds: Franck Montmessin (update 06/2003)
     
    249250     
    250251!$OMP THREADPRIVATE(fluxsurf_lw,fluxsurf_sw,fluxsurfabs_sw,fluxtop_lw,fluxabs_sw,fluxtop_dn,fluxdyn,OLR_nu,OSR_nu,&
    251        
     252       
    252253        !$OMP zdtlw,zdtsw,sensibFlux)
    253254
     
    270271      real dtlscale(ngrid,nlayer)                             ! Largescale routine.
    271272      real zdtc(ngrid,nlayer)                                 ! Condense_co2 routine.
    272       real zdtdif(ngrid,nlayer)                               ! Turbdiff/vdifc routines.
     273      real zdtdif(ngrid,nlayer)                                      ! Turbdiff/vdifc routines.
    273274      real zdtmr(ngrid,nlayer)                                ! Mass_redistribution routine.
    274275      real zdtrain(ngrid,nlayer)                              ! Rain routine.
     
    442443        ALLOCATE(tsoil(ngrid,nsoilmx))   
    443444        ALLOCATE(albedo(ngrid,L_NSPECTV))
    444         ALLOCATE(albedo_equivalent(ngrid))     
    445         ALLOCATE(albedo_snow_SPECTV(L_NSPECTV))
    446         ALLOCATE(albedo_co2_ice_SPECTV(L_NSPECTV))
    447         ALLOCATE(albedo_bareground(ngrid))           
     445         ALLOCATE(albedo_equivalent(ngrid))       
     446         ALLOCATE(albedo_snow_SPECTV(L_NSPECTV))
     447         ALLOCATE(albedo_co2_ice_SPECTV(L_NSPECTV))
     448         ALLOCATE(albedo_bareground(ngrid))           
    448449        ALLOCATE(rnat(ngrid))         
    449450        ALLOCATE(emis(ngrid))   
     
    534535!        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    535536         albedo(:,:)=0.0
    536          albedo_bareground(:)=0.0
    537          albedo_snow_SPECTV(:)=0.0
    538          albedo_co2_ice_SPECTV(:)=0.0
     537         albedo_bareground(:)=0.0
     538         albedo_snow_SPECTV(:)=0.0
     539         albedo_co2_ice_SPECTV(:)=0.0
    539540         call surfini(ngrid,nq,qsurf,albedo,albedo_bareground,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
    540541         
     
    736737              zlss=Mod(-(2.*pi*(zday/year_day)*nres - right_ascen),2.*pi)
    737738      elseif (diurnal) then
    738               zlss=-2.*pi*(zday-.5)
     739              zlss=-2.*pi*(zday-.5)
    739740      else if(diurnal .eqv. .false.) then
    740741              zlss=9999.
     
    782783            zh(ig,l)=pt(ig,l)/zpopsk(ig,l)
    783784            mass(ig,l)  = (pplev(ig,l) - pplev(ig,l+1))/glat(ig)
    784             massarea(ig,l)=mass(ig,l)*area(ig)
     785            massarea(ig,l)=mass(ig,l)*area(ig)
    785786         enddo
    786787      enddo
     
    845846                  call abort
    846847               endif
    847                if(water) then
     848               if(water) then
    848849                  muvar(1:ngrid,1:nlayer)=mugaz/(1.e0+(1.e0/epsi-1.e0)*pq(1:ngrid,1:nlayer,igcm_h2o_vap))
    849                   muvar(1:ngrid,nlayer+1)=mugaz/(1.e0+(1.e0/epsi-1.e0)*pq(1:ngrid,nlayer,igcm_h2o_vap))
    850                   ! take into account water effect on mean molecular weight
    851                else
     850                  muvar(1:ngrid,nlayer+1)=mugaz/(1.e0+(1.e0/epsi-1.e0)*pq(1:ngrid,nlayer,igcm_h2o_vap))
     851                  ! take into account water effect on mean molecular weight
     852               else
    852853                  muvar(1:ngrid,1:nlayer+1)=mugaz
    853                endif
     854               endif
    854855     
    855856
     
    904905                     zdtsw(ig,1:nlayer) = ntf*zdtsw1(ig,1:nlayer) + tf*zdtsw(ig,1:nlayer)
    905906
    906                      OSR_nu(ig,1:L_NSPECTV) = ntf*OSR_nu1(ig,1:L_NSPECTV) + tf*OSR_nu(ig,1:L_NSPECTV)                  
    907                      OLR_nu(ig,1:L_NSPECTI) = ntf*OLR_nu1(ig,1:L_NSPECTI) + tf*OLR_nu(ig,1:L_NSPECTI)                  
     907                     OSR_nu(ig,1:L_NSPECTV) = ntf*OSR_nu1(ig,1:L_NSPECTV) + tf*OSR_nu(ig,1:L_NSPECTV)                       
     908                     OLR_nu(ig,1:L_NSPECTI) = ntf*OLR_nu1(ig,1:L_NSPECTI) + tf*OLR_nu(ig,1:L_NSPECTI)                       
    908909                  enddo                               
    909910
     
    978979         !----------------------------
    979980         if(enertest)then
    980             call planetwide_sumval(cpp*massarea(:,:)*zdtsw(:,:)/totarea_planet,dEtotSW)
    981             call planetwide_sumval(cpp*massarea(:,:)*zdtlw(:,:)/totarea_planet,dEtotLW)
    982             !call planetwide_sumval(fluxsurf_sw(:)*(1.-albedo_equivalent(:))*area(:)/totarea_planet,dEtotsSW) !JL13 carefull, albedo can have changed since the last time we called corrk
     981            call planetwide_sumval(cpp*massarea(:,:)*zdtsw(:,:)/totarea_planet,dEtotSW)
     982            call planetwide_sumval(cpp*massarea(:,:)*zdtlw(:,:)/totarea_planet,dEtotLW)
     983            !call planetwide_sumval(fluxsurf_sw(:)*(1.-albedo_equivalent(:))*area(:)/totarea_planet,dEtotsSW) !JL13 carefull, albedo can have changed since the last time we called corrk
    983984            call planetwide_sumval(fluxsurfabs_sw(:)*area(:)/totarea_planet,dEtotsSW) !JL13 carefull, albedo can have changed since the last time we called corrk
    984             call planetwide_sumval((fluxsurf_lw(:)*emis(:)-zplanck(:))*area(:)/totarea_planet,dEtotsLW)
    985             dEzRadsw(:,:)=cpp*mass(:,:)*zdtsw(:,:)
    986             dEzRadlw(:,:)=cpp*mass(:,:)*zdtlw(:,:)
    987             if (is_master) then
     985            call planetwide_sumval((fluxsurf_lw(:)*emis(:)-zplanck(:))*area(:)/totarea_planet,dEtotsLW)
     986            dEzRadsw(:,:)=cpp*mass(:,:)*zdtsw(:,:)
     987            dEzRadlw(:,:)=cpp*mass(:,:)*zdtlw(:,:)
     988            if (is_master) then
    988989               print*,'---------------------------------------------------------------'
    989990               print*,'In corrk SW atmospheric heating       =',dEtotSW,' W m-2'
     
    993994               print*,'In corrk LW surface heating           =',dEtotsLW,' W m-2'
    994995               print*,'surface net rad heating (SW+LW)       =',dEtotsLW+dEtotsSW,' W m-2'
    995             endif
     996            endif
    996997         endif ! end of 'enertest'
    997998
     
    10091010
    10101011         ! JL12 the following if test is temporarily there to allow us to compare the old vdifc with turbdiff.
    1011         if (UseTurbDiff) then
    1012        
     1012        if (UseTurbDiff) then
     1013       
    10131014            call turbdiff(ngrid,nlayer,nq,rnat,                  &
    10141015                          ptimestep,capcal,lwrite,               &
     
    10171018                          pdt,pdq,zflubid,                       &
    10181019                          zdudif,zdvdif,zdtdif,zdtsdif,          &
    1019                           sensibFlux,q2,zdqdif,zdqevap,zdqsdif,  &
     1020                          sensibFlux,q2,zdqdif,zdqevap,zdqsdif,  &
    10201021                          taux,tauy,lastcall)
    10211022
    1022         else
    1023        
     1023        else
     1024       
    10241025            zdh(1:ngrid,1:nlayer)=pdt(1:ngrid,1:nlayer)/zpopsk(1:ngrid,1:nlayer)
    10251026 
     
    10301031                       zdh,pdq,zflubid,                       &
    10311032                       zdudif,zdvdif,zdhdif,zdtsdif,          &
    1032                        sensibFlux,q2,zdqdif,zdqsdif,          &
     1033                       sensibFlux,q2,zdqdif,zdqsdif,          &
    10331034                       taux,tauy,lastcall)
    10341035
    10351036            zdtdif(1:ngrid,1:nlayer)=zdhdif(1:ngrid,1:nlayer)*zpopsk(1:ngrid,1:nlayer) ! for diagnostic only
    1036             zdqevap(1:ngrid,1:nlayer)=0.
     1037            zdqevap(1:ngrid,1:nlayer)=0.
    10371038
    10381039         end if !end of 'UseTurbDiff'
     
    10601061         if(enertest)then
    10611062         
    1062             dEzdiff(:,:)=cpp*mass(:,:)*zdtdif(:,:)
     1063            dEzdiff(:,:)=cpp*mass(:,:)*zdtdif(:,:)
    10631064            do ig = 1, ngrid
    1064                dEdiff(ig)=SUM(dEzdiff (ig,:))+ sensibFlux(ig)! subtract flux to the ground
    1065                dEzdiff(ig,1)= dEzdiff(ig,1)+ sensibFlux(ig)! subtract flux to the ground
     1065               dEdiff(ig)=SUM(dEzdiff (ig,:))+ sensibFlux(ig)! subtract flux to the ground
     1066               dEzdiff(ig,1)= dEzdiff(ig,1)+ sensibFlux(ig)! subtract flux to the ground
    10661067            enddo
    10671068           
    1068             call planetwide_sumval(dEdiff(:)*area(:)/totarea_planet,dEtot)
    1069             dEdiffs(:)=capcal(:)*zdtsdif(:)-zflubid(:)-sensibFlux(:)
    1070             call planetwide_sumval(dEdiffs(:)*area(:)/totarea_planet,dEtots)
    1071             call planetwide_sumval(sensibFlux(:)*area(:)/totarea_planet,AtmToSurf_TurbFlux)
     1069            call planetwide_sumval(dEdiff(:)*area(:)/totarea_planet,dEtot)
     1070            dEdiffs(:)=capcal(:)*zdtsdif(:)-zflubid(:)-sensibFlux(:)
     1071            call planetwide_sumval(dEdiffs(:)*area(:)/totarea_planet,dEtots)
     1072            call planetwide_sumval(sensibFlux(:)*area(:)/totarea_planet,AtmToSurf_TurbFlux)
    10721073           
    1073             if (is_master) then
     1074            if (is_master) then
    10741075           
    10751076               if (UseTurbDiff) then
    1076                   print*,'In TurbDiff sensible flux (atm=>surf) =',AtmToSurf_TurbFlux,' W m-2'
    1077                   print*,'In TurbDiff non-cons atm nrj change   =',dEtot,' W m-2'
     1077                         print*,'In TurbDiff sensible flux (atm=>surf) =',AtmToSurf_TurbFlux,' W m-2'
     1078                         print*,'In TurbDiff non-cons atm nrj change   =',dEtot,' W m-2'
    10781079                  print*,'In TurbDiff (correc rad+latent heat) surf nrj change =',dEtots,' W m-2'
    1079                else
    1080                   print*,'In vdifc sensible flux (atm=>surf)    =',AtmToSurf_TurbFlux,' W m-2'
    1081                   print*,'In vdifc non-cons atm nrj change      =',dEtot,' W m-2'
    1082                   print*,'In vdifc (correc rad+latent heat) surf nrj change =',dEtots,' W m-2'
    1083                end if
    1084             endif ! end of 'is_master'
     1080               else
     1081                         print*,'In vdifc sensible flux (atm=>surf)    =',AtmToSurf_TurbFlux,' W m-2'
     1082                         print*,'In vdifc non-cons atm nrj change      =',dEtot,' W m-2'
     1083                         print*,'In vdifc (correc rad+latent heat) surf nrj change =',dEtots,' W m-2'
     1084               end if
     1085            endif ! end of 'is_master'
    10851086           
    10861087         ! JL12 : note that the black body radiative flux emitted by the surface has been updated by the implicit scheme but not given back elsewhere.
     
    10911092         if(watertest.and.water)then
    10921093         
    1093             call planetwide_sumval(massarea(:,:)*zdqdif(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dWtot_tmp)
    1094             call planetwide_sumval(zdqsdif(:,igcm_h2o_vap)*area(:)*ptimestep/totarea_planet,dWtots_tmp)
     1094            call planetwide_sumval(massarea(:,:)*zdqdif(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dWtot_tmp)
     1095            call planetwide_sumval(zdqsdif(:,igcm_h2o_vap)*area(:)*ptimestep/totarea_planet,dWtots_tmp)
    10951096            do ig = 1, ngrid
    1096                vdifcncons(ig)=SUM(mass(ig,:)*zdqdif(ig,:,igcm_h2o_vap))
    1097             enddo
    1098             call planetwide_sumval(massarea(:,:)*zdqdif(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
    1099             call planetwide_sumval(zdqsdif(:,igcm_h2o_ice)*area(:)*ptimestep/totarea_planet,dWtots)
    1100             dWtot = dWtot + dWtot_tmp
    1101             dWtots = dWtots + dWtots_tmp
     1097               vdifcncons(ig)=SUM(mass(ig,:)*zdqdif(ig,:,igcm_h2o_vap))
     1098            enddo
     1099            call planetwide_sumval(massarea(:,:)*zdqdif(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
     1100            call planetwide_sumval(zdqsdif(:,igcm_h2o_ice)*area(:)*ptimestep/totarea_planet,dWtots)
     1101            dWtot = dWtot + dWtot_tmp
     1102            dWtots = dWtots + dWtots_tmp
    11021103            do ig = 1, ngrid
    1103                vdifcncons(ig)=vdifcncons(ig) + SUM(mass(ig,:)*zdqdif(ig,:,igcm_h2o_ice))
    1104             enddo          
    1105             call planetwide_maxval(vdifcncons(:),nconsMAX)
    1106 
    1107             if (is_master) then
     1104               vdifcncons(ig)=vdifcncons(ig) + SUM(mass(ig,:)*zdqdif(ig,:,igcm_h2o_ice))
     1105            enddo           
     1106            call planetwide_maxval(vdifcncons(:),nconsMAX)
     1107
     1108            if (is_master) then
    11081109               print*,'---------------------------------------------------------------'
    11091110               print*,'In difv atmospheric water change        =',dWtot,' kg m-2'
     
    11111112               print*,'In difv non-cons factor                 =',dWtot+dWtots,' kg m-2'
    11121113               print*,'In difv MAX non-cons factor             =',nconsMAX,' kg m-2 s-1'
    1113             endif
     1114            endif
    11141115
    11151116         endif ! end of 'watertest'
     
    11571158         ! Test energy conservation
    11581159         if(enertest)then
    1159             call planetwide_sumval(cpp*massarea(:,:)*zdtadj(:,:)/totarea_planet,dEtot)
     1160            call planetwide_sumval(cpp*massarea(:,:)*zdtadj(:,:)/totarea_planet,dEtot)
    11601161            if (is_master) print*,'In convadj atmospheric energy change  =',dEtot,' W m-2'
    11611162         endif
     
    11631164         ! Test water conservation
    11641165         if(watertest)then
    1165             call planetwide_sumval(massarea(:,:)*zdqadj(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dWtot_tmp)
     1166            call planetwide_sumval(massarea(:,:)*zdqadj(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dWtot_tmp)
    11661167            do ig = 1, ngrid
    1167                cadjncons(ig)=SUM(mass(ig,:)*zdqadj(ig,:,igcm_h2o_vap))
    1168             enddo
    1169             call planetwide_sumval(massarea(:,:)*zdqadj(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
    1170             dWtot = dWtot + dWtot_tmp
     1168               cadjncons(ig)=SUM(mass(ig,:)*zdqadj(ig,:,igcm_h2o_vap))
     1169            enddo
     1170            call planetwide_sumval(massarea(:,:)*zdqadj(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
     1171            dWtot = dWtot + dWtot_tmp
    11711172            do ig = 1, ngrid
    1172                cadjncons(ig)=cadjncons(ig) + SUM(mass(ig,:)*zdqadj(ig,:,igcm_h2o_ice))
    1173             enddo          
    1174             call planetwide_maxval(cadjncons(:),nconsMAX)
     1173               cadjncons(ig)=cadjncons(ig) + SUM(mass(ig,:)*zdqadj(ig,:,igcm_h2o_ice))
     1174            enddo           
     1175            call planetwide_maxval(cadjncons(:),nconsMAX)
    11751176
    11761177            if (is_master) then
    1177                print*,'In convadj atmospheric water change     =',dWtot,' kg m-2'
     1178               print*,'In convadj atmospheric water change     =',dWtot,' kg m-2'
    11781179               print*,'In convadj MAX non-cons factor          =',nconsMAX,' kg m-2 s-1'
    1179             endif
     1180            endif
    11801181           
    11811182         endif ! end of 'watertest'
     
    12081209         ! test energy conservation
    12091210         if(enertest)then
    1210             call planetwide_sumval(cpp*massarea(:,:)*zdtc(:,:)/totarea_planet,dEtot)
    1211             call planetwide_sumval(capcal(:)*zdtsurfc(:)*area(:)/totarea_planet,dEtots)
    1212             if (is_master) then
    1213                print*,'In co2cloud atmospheric energy change   =',dEtot,' W m-2'
     1211            call planetwide_sumval(cpp*massarea(:,:)*zdtc(:,:)/totarea_planet,dEtot)
     1212            call planetwide_sumval(capcal(:)*zdtsurfc(:)*area(:)/totarea_planet,dEtots)
     1213            if (is_master) then
     1214               print*,'In co2cloud atmospheric energy change   =',dEtot,' W m-2'
    12141215               print*,'In co2cloud surface energy change       =',dEtots,' W m-2'
    1215             endif
     1216            endif
    12161217         endif
    12171218
     
    12331234            if(watercond.and.(RLVTT.gt.1.e-8))then
    12341235
    1235                dqmoist(1:ngrid,1:nlayer,1:nq)=0.
    1236                dtmoist(1:ngrid,1:nlayer)=0.
     1236               dqmoist(1:ngrid,1:nlayer,1:nq)=0.
     1237               dtmoist(1:ngrid,1:nlayer)=0.
    12371238               
    12381239               ! Moist Convective Adjustment.
    12391240               ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    1240                call moistadj(ngrid,nlayer,nq,pt,pq,pdq,pplev,pplay,dtmoist,dqmoist,ptimestep,rneb_man)
     1241               call moistadj(ngrid,nlayer,nq,pt,pq,pdq,pplev,pplay,dtmoist,dqmoist,ptimestep,rneb_man)
    12411242
    12421243               pdq(1:ngrid,1:nlayer,igcm_h2o_vap) = pdq(1:ngrid,1:nlayer,igcm_h2o_vap)     &
    1243                                                   + dqmoist(1:ngrid,1:nlayer,igcm_h2o_vap)
     1244                                                  + dqmoist(1:ngrid,1:nlayer,igcm_h2o_vap)
    12441245               pdq(1:ngrid,1:nlayer,igcm_h2o_ice) = pdq(1:ngrid,1:nlayer,igcm_h2o_ice)     &
    12451246                                                  + dqmoist(1:ngrid,1:nlayer,igcm_h2o_ice)
     
    12491250               if(enertest)then
    12501251               
    1251                   call planetwide_sumval(cpp*massarea(:,:)*dtmoist(:,:)/totarea_planet,dEtot)
    1252                   call planetwide_maxval(dtmoist(:,:),dtmoist_max)
    1253                   call planetwide_minval(dtmoist(:,:),dtmoist_min)
    1254                   madjdEz(:,:)=cpp*mass(:,:)*dtmoist(:,:)
     1252                  call planetwide_sumval(cpp*massarea(:,:)*dtmoist(:,:)/totarea_planet,dEtot)
     1253                  call planetwide_maxval(dtmoist(:,:),dtmoist_max)
     1254                  call planetwide_minval(dtmoist(:,:),dtmoist_min)
     1255                  madjdEz(:,:)=cpp*mass(:,:)*dtmoist(:,:)
    12551256                  do ig=1,ngrid
    12561257                     madjdE(ig) = cpp*SUM(mass(:,:)*dtmoist(:,:))
    12571258                  enddo
    12581259                 
    1259                   if (is_master) then
     1260                  if (is_master) then
    12601261                     print*,'In moistadj atmospheric energy change   =',dEtot,' W m-2'
    12611262                     print*,'In moistadj MAX atmospheric energy change   =',dtmoist_max*ptimestep,'K/step'
    12621263                     print*,'In moistadj MIN atmospheric energy change   =',dtmoist_min*ptimestep,'K/step'
    1263                   endif
    1264                  
    1265                   call planetwide_sumval(massarea(:,:)*dqmoist(:,:,igcm_h2o_vap)*ptimestep/totarea_planet+      &
    1266                                          massarea(:,:)*dqmoist(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
    1267                   if (is_master) print*,'In moistadj atmospheric water change    =',dWtot,' kg m-2'
     1264                  endif
     1265                 
     1266                  call planetwide_sumval(massarea(:,:)*dqmoist(:,:,igcm_h2o_vap)*ptimestep/totarea_planet+        &
     1267                                           massarea(:,:)*dqmoist(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
     1268                  if (is_master) print*,'In moistadj atmospheric water change    =',dWtot,' kg m-2'
    12681269                 
    12691270               endif ! end of 'enertest'
    1270                
     1271               
    12711272
    12721273               ! Large scale condensation/evaporation.
     
    12841285                     lscaledE(ig) = cpp*SUM(mass(:,:)*dtlscale(:,:))
    12851286                  enddo
    1286                   call planetwide_sumval(cpp*massarea(:,:)*dtlscale(:,:)/totarea_planet,dEtot)
    1287 
    1288                   if (is_master) print*,'In largescale atmospheric energy change =',dEtot,' W m-2'
     1287                  call planetwide_sumval(cpp*massarea(:,:)*dtlscale(:,:)/totarea_planet,dEtot)
     1288
     1289                  if (is_master) print*,'In largescale atmospheric energy change =',dEtot,' W m-2'
    12891290
    12901291                  ! Test water conservation.
    1291                   call planetwide_sumval(massarea(:,:)*dqvaplscale(:,:)*ptimestep/totarea_planet+       &
    1292                                          SUM(massarea(:,:)*dqcldlscale(:,:))*ptimestep/totarea_planet,dWtot)
     1292                  call planetwide_sumval(massarea(:,:)*dqvaplscale(:,:)*ptimestep/totarea_planet+        &
     1293                                           SUM(massarea(:,:)*dqcldlscale(:,:))*ptimestep/totarea_planet,dWtot)
    12931294                       
    1294                   if (is_master) print*,'In largescale atmospheric water change  =',dWtot,' kg m-2'
     1295                  if (is_master) print*,'In largescale atmospheric water change  =',dWtot,' kg m-2'
    12951296               endif ! end of 'enertest'
    12961297
     
    13161317
    13171318               pdq(1:ngrid,1:nlayer,igcm_h2o_vap) = pdq(1:ngrid,1:nlayer,igcm_h2o_vap) &
    1318                                                   + zdqrain(1:ngrid,1:nlayer,igcm_h2o_vap)
     1319                                                  + zdqrain(1:ngrid,1:nlayer,igcm_h2o_vap)
    13191320               pdq(1:ngrid,1:nlayer,igcm_h2o_ice) = pdq(1:ngrid,1:nlayer,igcm_h2o_ice) &
    1320                                                   + zdqrain(1:ngrid,1:nlayer,igcm_h2o_ice)
     1321                                                  + zdqrain(1:ngrid,1:nlayer,igcm_h2o_ice)
    13211322               pdt(1:ngrid,1:nlayer) = pdt(1:ngrid,1:nlayer)+zdtrain(1:ngrid,1:nlayer)
    13221323               
     
    13271328               if(enertest)then
    13281329               
    1329                   call planetwide_sumval(cpp*massarea(:,:)*zdtrain(:,:)/totarea_planet,dEtot)
    1330                   if (is_master) print*,'In rain atmospheric T energy change       =',dEtot,' W m-2'
    1331                   call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_ice)/totarea_planet*RLVTT/cpp,dItot_tmp)
    1332                   call planetwide_sumval(area(:)*zdqssnow(:)/totarea_planet*RLVTT/cpp,dItot)
    1333                   dItot = dItot + dItot_tmp
    1334                   call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dVtot_tmp)
    1335                   call planetwide_sumval(area(:)*zdqsrain(:)/totarea_planet*RLVTT/cpp,dVtot)
    1336                   dVtot = dVtot + dVtot_tmp
    1337                   dEtot = dItot + dVtot
     1330                  call planetwide_sumval(cpp*massarea(:,:)*zdtrain(:,:)/totarea_planet,dEtot)
     1331                  if (is_master) print*,'In rain atmospheric T energy change       =',dEtot,' W m-2'
     1332                  call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_ice)/totarea_planet*RLVTT/cpp,dItot_tmp)
     1333                  call planetwide_sumval(area(:)*zdqssnow(:)/totarea_planet*RLVTT/cpp,dItot)
     1334                  dItot = dItot + dItot_tmp
     1335                  call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_vap)*ptimestep/totarea_planet,dVtot_tmp)
     1336                  call planetwide_sumval(area(:)*zdqsrain(:)/totarea_planet*RLVTT/cpp,dVtot)
     1337                  dVtot = dVtot + dVtot_tmp
     1338                  dEtot = dItot + dVtot
    13381339                 
    1339                   if (is_master) then
     1340                  if (is_master) then
    13401341                     print*,'In rain dItot =',dItot,' W m-2'
    13411342                     print*,'In rain dVtot =',dVtot,' W m-2'
    13421343                     print*,'In rain atmospheric L energy change       =',dEtot,' W m-2'
    1343                   endif
     1344                  endif
    13441345
    13451346                  ! Test water conservation
    1346                   call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_vap)*ptimestep/totarea_planet+      &
    1347                         massarea(:,:)*zdqrain(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
    1348                   call planetwide_sumval((zdqsrain(:)+zdqssnow(:))*area(:)*ptimestep/totarea_planet,dWtots)
     1347                  call planetwide_sumval(massarea(:,:)*zdqrain(:,:,igcm_h2o_vap)*ptimestep/totarea_planet+        &
     1348                          massarea(:,:)*zdqrain(:,:,igcm_h2o_ice)*ptimestep/totarea_planet,dWtot)
     1349                  call planetwide_sumval((zdqsrain(:)+zdqssnow(:))*area(:)*ptimestep/totarea_planet,dWtots)
    13491350                 
    1350                   if (is_master) then
    1351                         print*,'In rain atmospheric water change        =',dWtot,' kg m-2'
    1352                         print*,'In rain surface water change            =',dWtots,' kg m-2'
    1353                         print*,'In rain non-cons factor                 =',dWtot+dWtots,' kg m-2'
    1354                   endif
     1351                  if (is_master) then
     1352                          print*,'In rain atmospheric water change        =',dWtot,' kg m-2'
     1353                          print*,'In rain surface water change            =',dWtots,' kg m-2'
     1354                          print*,'In rain non-cons factor                 =',dWtot+dWtots,' kg m-2'
     1355                  endif
    13551356                 
    13561357               endif ! end of 'enertest'
     
    13731374           
    13741375               iq=igcm_h2o_ice
    1375                call planetwide_sumval(massarea(:,:)*pq(:,:,iq)*ptimestep/totarea_planet,dWtot)
    1376                call planetwide_sumval(massarea(:,:)*pdq(:,:,iq)*ptimestep/totarea_planet,dWtots)
    1377                if (is_master) then
    1378                   print*,'Before sedim pq  =',dWtot,' kg m-2'
     1376               call planetwide_sumval(massarea(:,:)*pq(:,:,iq)*ptimestep/totarea_planet,dWtot)
     1377               call planetwide_sumval(massarea(:,:)*pdq(:,:,iq)*ptimestep/totarea_planet,dWtots)
     1378               if (is_master) then
     1379                        print*,'Before sedim pq  =',dWtot,' kg m-2'
    13791380                  print*,'Before sedim pdq =',dWtots,' kg m-2'
    1380                endif
     1381               endif
    13811382            endif
    13821383           
     
    13871388            if(watertest)then
    13881389               iq=igcm_h2o_ice
    1389                call planetwide_sumval(massarea(:,:)*pq(:,:,iq)*ptimestep/totarea_planet,dWtot)
    1390                call planetwide_sumval(massarea(:,:)*pdq(:,:,iq)*ptimestep/totarea_planet,dWtots)
    1391                if (is_master) then
    1392                   print*,'After sedim pq  =',dWtot,' kg m-2'
    1393                   print*,'After sedim pdq =',dWtots,' kg m-2'
    1394                endif
     1390               call planetwide_sumval(massarea(:,:)*pq(:,:,iq)*ptimestep/totarea_planet,dWtot)
     1391               call planetwide_sumval(massarea(:,:)*pdq(:,:,iq)*ptimestep/totarea_planet,dWtots)
     1392               if (is_master) then
     1393                        print*,'After sedim pq  =',dWtot,' kg m-2'
     1394                        print*,'After sedim pdq =',dWtots,' kg m-2'
     1395                 endif
    13951396            endif
    13961397
     
    14011402            ! Test water conservation
    14021403            if(watertest)then
    1403                call planetwide_sumval(massarea(:,:)*(zdqsed(:,:,igcm_h2o_vap)+zdqsed(:,:,igcm_h2o_ice))*ptimestep/totarea_planet,dWtot)
    1404                call planetwide_sumval((zdqssed(:,igcm_h2o_vap)+zdqssed(:,igcm_h2o_ice))*area(:)*ptimestep/totarea_planet,dWtots)
    1405                if (is_master) then
    1406                   print*,'In sedim atmospheric ice change         =',dWtot,' kg m-2'
    1407                   print*,'In sedim surface ice change             =',dWtots,' kg m-2'
    1408                   print*,'In sedim non-cons factor                =',dWtot+dWtots,' kg m-2'
    1409                endif
     1404               call planetwide_sumval(massarea(:,:)*(zdqsed(:,:,igcm_h2o_vap)+zdqsed(:,:,igcm_h2o_ice))*ptimestep/totarea_planet,dWtot)
     1405               call planetwide_sumval((zdqssed(:,igcm_h2o_vap)+zdqssed(:,igcm_h2o_ice))*area(:)*ptimestep/totarea_planet,dWtots)
     1406               if (is_master) then
     1407                        print*,'In sedim atmospheric ice change         =',dWtot,' kg m-2'
     1408                        print*,'In sedim surface ice change             =',dWtots,' kg m-2'
     1409                        print*,'In sedim non-cons factor                =',dWtot+dWtots,' kg m-2'
     1410               endif
    14101411            endif
    14111412
     
    14211422
    14221423            zdmassmr(1:ngrid,1:nlayer) = mass(1:ngrid,1:nlayer) *     &
    1423                (   zdqevap(1:ngrid,1:nlayer)                          &
    1424                  + zdqrain(1:ngrid,1:nlayer,igcm_h2o_vap)             &
    1425                 + dqmoist(1:ngrid,1:nlayer,igcm_h2o_vap)             &
    1426                 + dqvaplscale(1:ngrid,1:nlayer) )
     1424               (   zdqevap(1:ngrid,1:nlayer)                          &
     1425                 + zdqrain(1:ngrid,1:nlayer,igcm_h2o_vap)             &
     1426                + dqmoist(1:ngrid,1:nlayer,igcm_h2o_vap)             &
     1427                + dqvaplscale(1:ngrid,1:nlayer) )
    14271428
    14281429            do ig = 1, ngrid
    1429                zdmassmr_col(ig)=SUM(zdmassmr(ig,1:nlayer))
     1430               zdmassmr_col(ig)=SUM(zdmassmr(ig,1:nlayer))
    14301431            enddo
    14311432           
    1432             call writediagfi(ngrid,"mass_evap","mass gain"," ",3,zdmassmr)
    1433             call writediagfi(ngrid,"mass_evap_col","mass gain col"," ",2,zdmassmr_col)
    1434             call writediagfi(ngrid,"mass","mass","kg/m2",3,mass)
    1435 
    1436             call mass_redistribution(ngrid,nlayer,nq,ptimestep,                     &
     1433            call writediagfi(ngrid,"mass_evap","mass gain"," ",3,zdmassmr)
     1434            call writediagfi(ngrid,"mass_evap_col","mass gain col"," ",2,zdmassmr_col)
     1435            call writediagfi(ngrid,"mass","mass","kg/m2",3,mass)
     1436
     1437            call mass_redistribution(ngrid,nlayer,nq,ptimestep,                     &
    14371438                                     rnat,capcal,pplay,pplev,pt,tsurf,pq,qsurf,     &
    1438                                      pu,pv,pdt,zdtsurf,pdq,pdu,pdv,zdmassmr,        &
    1439                                      zdtmr,zdtsurfmr,zdpsrfmr,zdumr,zdvmr,zdqmr,zdqsurfmr)
    1440        
     1439                                     pu,pv,pdt,zdtsurf,pdq,pdu,pdv,zdmassmr,        &
     1440                                     zdtmr,zdtsurfmr,zdpsrfmr,zdumr,zdvmr,zdqmr,zdqsurfmr)
     1441       
    14411442            pdq(1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqmr(1:ngrid,1:nlayer,1:nq)
    14421443            dqsurf(1:ngrid,1:nq)       = dqsurf(1:ngrid,1:nq) + zdqsurfmr(1:ngrid,1:nq)
     
    14441445            pdu(1:ngrid,1:nlayer)      = pdu(1:ngrid,1:nlayer) + zdumr(1:ngrid,1:nlayer)
    14451446            pdv(1:ngrid,1:nlayer)      = pdv(1:ngrid,1:nlayer) + zdvmr(1:ngrid,1:nlayer)
    1446             pdpsrf(1:ngrid)            = pdpsrf(1:ngrid) + zdpsrfmr(1:ngrid)
     1447            pdpsrf(1:ngrid)            = pdpsrf(1:ngrid) + zdpsrfmr(1:ngrid)
    14471448            zdtsurf(1:ngrid)           = zdtsurf(1:ngrid) + zdtsurfmr(1:ngrid)
    1448            
    1449         endif
     1449           
     1450        endif
    14501451
    14511452  ! ------------------
     
    14931494            call hydrol(ngrid,nq,ptimestep,rnat,tsurf,qsurf,dqsurf,dqs_hyd, &
    14941495                        capcal,albedo,albedo_bareground,                    &
    1495                         albedo_snow_SPECTV,albedo_co2_ice_SPECTV,           &
     1496                        albedo_snow_SPECTV,albedo_co2_ice_SPECTV,           &
    14961497                        mu0,zdtsurf,zdtsurf_hyd,hice,pctsrf_sic,            &
    14971498                        sea_ice)
     
    15041505            ! Test energy conservation
    15051506            if(enertest)then
    1506                call planetwide_sumval(area(:)*capcal(:)*zdtsurf_hyd(:)/totarea_planet,dEtots)
    1507                if (is_master) print*,'In hydrol surface energy change     =',dEtots,' W m-2'
     1507               call planetwide_sumval(area(:)*capcal(:)*zdtsurf_hyd(:)/totarea_planet,dEtots)
     1508               if (is_master) print*,'In hydrol surface energy change     =',dEtots,' W m-2'
    15081509            endif
    15091510
    15101511            ! test water conservation
    15111512            if(watertest)then
    1512                call planetwide_sumval(dqs_hyd(:,igcm_h2o_ice)*area(:)*ptimestep/totarea_planet,dWtots)
    1513                if (is_master) print*,'In hydrol surface ice change            =',dWtots,' kg m-2'
    1514                   call planetwide_sumval(dqs_hyd(:,igcm_h2o_vap)*area(:)*ptimestep/totarea_planet,dWtots)
    1515                if (is_master) then
     1513               call planetwide_sumval(dqs_hyd(:,igcm_h2o_ice)*area(:)*ptimestep/totarea_planet,dWtots)
     1514               if (is_master) print*,'In hydrol surface ice change            =',dWtots,' kg m-2'
     1515                  call planetwide_sumval(dqs_hyd(:,igcm_h2o_vap)*area(:)*ptimestep/totarea_planet,dWtots)
     1516               if (is_master) then
    15161517                  print*,'In hydrol surface water change          =',dWtots,' kg m-2'
    15171518                  print*,'---------------------------------------------------------------'
    1518                endif
     1519               endif
    15191520            endif
    15201521
     
    15901591      ! Test energy conservation
    15911592      if(enertest)then
    1592          call planetwide_sumval(area(:)*capcal(:)*zdtsurf(:)/totarea_planet,dEtots)     
    1593         if (is_master) print*,'Surface energy change                 =',dEtots,' W m-2'
     1593         call planetwide_sumval(area(:)*capcal(:)*zdtsurf(:)/totarea_planet,dEtots)       
     1594        if (is_master) print*,'Surface energy change                 =',dEtots,' W m-2'
    15941595      endif
    15951596
     
    16381639         print*,Ts1,Ts2,Ts3,TsS
    16391640      else
    1640         if (is_master) then
     1641              if (is_master) then
    16411642            print*,'  ave[Tsurf]     min[Tsurf]     max[Tsurf]'
    16421643            print*,Ts1,Ts2,Ts3
    1643         endif
     1644        endif
    16441645      end if
    16451646
     
    16481649      if(corrk)then
    16491650
    1650         call planetwide_sumval(area(:)*fluxtop_dn(:)/totarea_planet,ISR)
    1651         call planetwide_sumval(area(:)*fluxabs_sw(:)/totarea_planet,ASR)
    1652         call planetwide_sumval(area(:)*fluxtop_lw(:)/totarea_planet,OLR)
    1653         call planetwide_sumval(area(:)*fluxgrd(:)/totarea_planet,GND)
    1654         call planetwide_sumval(area(:)*fluxdyn(:)/totarea_planet,DYN)
     1651        call planetwide_sumval(area(:)*fluxtop_dn(:)/totarea_planet,ISR)
     1652        call planetwide_sumval(area(:)*fluxabs_sw(:)/totarea_planet,ASR)
     1653        call planetwide_sumval(area(:)*fluxtop_lw(:)/totarea_planet,OLR)
     1654        call planetwide_sumval(area(:)*fluxgrd(:)/totarea_planet,GND)
     1655        call planetwide_sumval(area(:)*fluxdyn(:)/totarea_planet,DYN)
    16551656         do ig=1,ngrid
    16561657            if(fluxtop_dn(ig).lt.0.0)then
     
    16681669            DYN=0.0
    16691670         endif
    1670        
    1671         if (is_master) then
     1671       
     1672        if (is_master) then
    16721673            print*,'  ISR            ASR            OLR            GND            DYN [W m^-2]'
    16731674            print*, ISR,ASR,OLR,GND,DYN
    1674         endif
     1675        endif
    16751676
    16761677         if(enertest .and. is_master)then
     
    16881689               open(93,file="tem_bal.out",form='formatted',position='append')
    16891690               if(callsoil)then
    1690                   write(93,*) zday,Ts1,Ts2,Ts3,TsS
    1691                else
    1692                   write(93,*) zday,Ts1,Ts2,Ts3
    1693                endif
     1691                         write(93,*) zday,Ts1,Ts2,Ts3,TsS
     1692               else
     1693                  write(93,*) zday,Ts1,Ts2,Ts3
     1694               endif
    16941695               close(93)
    16951696            endif
     
    17441745      if(water)then
    17451746
    1746         call planetwide_sumval(area(:)*qsurf_hist(:,igcm_h2o_ice)/totarea_planet,icesrf)
    1747         call planetwide_sumval(area(:)*qsurf_hist(:,igcm_h2o_vap)/totarea_planet,liqsrf)
    1748         call planetwide_sumval(area(:)*qcol(:,igcm_h2o_ice)/totarea_planet,icecol)
    1749         call planetwide_sumval(area(:)*qcol(:,igcm_h2o_vap)/totarea_planet,vapcol)
     1747        call planetwide_sumval(area(:)*qsurf_hist(:,igcm_h2o_ice)/totarea_planet,icesrf)
     1748        call planetwide_sumval(area(:)*qsurf_hist(:,igcm_h2o_vap)/totarea_planet,liqsrf)
     1749        call planetwide_sumval(area(:)*qcol(:,igcm_h2o_ice)/totarea_planet,icecol)
     1750        call planetwide_sumval(area(:)*qcol(:,igcm_h2o_vap)/totarea_planet,vapcol)
    17501751
    17511752         h2otot = icesrf + liqsrf + icecol + vapcol
    1752        
    1753         if (is_master) then
     1753       
     1754        if (is_master) then
    17541755            print*,' Total water amount [kg m^-2]: ',h2otot
    17551756            print*,' Surface ice    Surface liq.   Atmos. con.     Atmos. vap. [kg m^-2] '
    17561757            print*, icesrf,liqsrf,icecol,vapcol
    1757         endif
     1758        endif
    17581759
    17591760         if(meanOLR .and. is_master)then
     
    20132014         
    20142015      endif ! end of 'callrad'
    2015        
     2016       
    20162017      if(enertest) then
    20172018     
    2018         if (calldifv) then
    2019          
    2020             call writediagfi(ngrid,"q2","turbulent kinetic energy","J.kg^-1",3,q2)
     2019        if (calldifv) then
     2020         
     2021            call writediagfi(ngrid,"q2","turbulent kinetic energy","J.kg^-1",3,q2)
    20212022            call writediagfi(ngrid,"sensibFlux","sensible heat flux","w.m^-2",2,sensibFlux)
    20222023           
    2023 !            call writediagfi(ngrid,"dEzdiff","turbulent diffusion heating (-sensible flux)","w.m^-2",3,dEzdiff)
    2024 !            call writediagfi(ngrid,"dEdiff","integrated turbulent diffusion heating (-sensible flux)","w.m^-2",2,dEdiff)
    2025 !            call writediagfi(ngrid,"dEdiffs","In TurbDiff (correc rad+latent heat) surf nrj change","w.m^-2",2,dEdiffs)
    2026              
    2027         endif
     2024!             call writediagfi(ngrid,"dEzdiff","turbulent diffusion heating (-sensible flux)","w.m^-2",3,dEzdiff)
     2025!             call writediagfi(ngrid,"dEdiff","integrated turbulent diffusion heating (-sensible flux)","w.m^-2",2,dEdiff)
     2026!             call writediagfi(ngrid,"dEdiffs","In TurbDiff (correc rad+latent heat) surf nrj change","w.m^-2",2,dEdiffs)
     2027             
     2028        endif
    20282029         
    2029         if (corrk) then
    2030             call writediagfi(ngrid,"dEzradsw","radiative heating","w.m^-2",3,dEzradsw)
    2031             call writediagfi(ngrid,"dEzradlw","radiative heating","w.m^-2",3,dEzradlw)
    2032         endif
     2030        if (corrk) then
     2031            call writediagfi(ngrid,"dEzradsw","radiative heating","w.m^-2",3,dEzradsw)
     2032            call writediagfi(ngrid,"dEzradlw","radiative heating","w.m^-2",3,dEzradlw)
     2033        endif
    20332034         
    20342035         if(watercond) then
    20352036
    2036             call writediagfi(ngrid,"lscaledE","heat from largescale","W m-2",2,lscaledE)
    2037             call writediagfi(ngrid,"madjdE","heat from moistadj","W m-2",2,madjdE)
    2038             call writediagfi(ngrid,"qsatatm","atm qsat"," ",3,qsat)
     2037            call writediagfi(ngrid,"lscaledE","heat from largescale","W m-2",2,lscaledE)
     2038            call writediagfi(ngrid,"madjdE","heat from moistadj","W m-2",2,madjdE)
     2039            call writediagfi(ngrid,"qsatatm","atm qsat"," ",3,qsat)
    20392040             
    2040 !            call writediagfi(ngrid,"lscaledEz","heat from largescale","W m-2",3,lscaledEz)
    2041 !            call writediagfi(ngrid,"madjdEz","heat from moistadj","W m-2",3,madjdEz)             
    2042 !            call writediagfi(ngrid,"h2o_max_col","maximum H2O column amount","kg.m^-2",2,H2Omaxcol)
     2041!             call writediagfi(ngrid,"lscaledEz","heat from largescale","W m-2",3,lscaledEz)
     2042!             call writediagfi(ngrid,"madjdEz","heat from moistadj","W m-2",3,madjdEz)             
     2043!             call writediagfi(ngrid,"h2o_max_col","maximum H2O column amount","kg.m^-2",2,H2Omaxcol)
    20432044
    20442045         endif
     
    20602061      ! Output aerosols.
    20612062      if (igcm_co2_ice.ne.0.and.iaero_co2.ne.0) &
    2062         call writediagfi(ngrid,'CO2ice_reff','CO2ice_reff','m',3,reffrad(1,1,iaero_co2))
     2063        call writediagfi(ngrid,'CO2ice_reff','CO2ice_reff','m',3,reffrad(1,1,iaero_co2))
    20632064      if (igcm_h2o_ice.ne.0.and.iaero_h2o.ne.0) &
    2064         call writediagfi(ngrid,'H2Oice_reff','H2Oice_reff','m',3,reffrad(:,:,iaero_h2o))
     2065        call writediagfi(ngrid,'H2Oice_reff','H2Oice_reff','m',3,reffrad(:,:,iaero_h2o))
    20652066      if (igcm_co2_ice.ne.0.and.iaero_co2.ne.0) &
    2066         call writediagfi(ngrid,'CO2ice_reffcol','CO2ice_reffcol','um kg m^-2',2,reffcol(1,iaero_co2))
     2067        call writediagfi(ngrid,'CO2ice_reffcol','CO2ice_reffcol','um kg m^-2',2,reffcol(1,iaero_co2))
    20672068      if (igcm_h2o_ice.ne.0.and.iaero_h2o.ne.0) &
    2068         call writediagfi(ngrid,'H2Oice_reffcol','H2Oice_reffcol','um kg m^-2',2,reffcol(1,iaero_h2o))
     2069        call writediagfi(ngrid,'H2Oice_reffcol','H2Oice_reffcol','um kg m^-2',2,reffcol(1,iaero_h2o))
    20692070
    20702071      ! Output tracers.
     
    20862087               call writediagfi(ngrid,"CLF","H2O cloud fraction"," ",3,cloudfrac)
    20872088               call writediagfi(ngrid,"CLFt","H2O column cloud fraction"," ",2,totcloudfrac)
    2088                call writediagfi(ngrid,"RH","relative humidity"," ",3,RH)
     2089               call writediagfi(ngrid,"RH","relative humidity"," ",3,RH)
    20892090            endif
    20902091
  • trunk/LMDZ.GENERIC/libf/phystd/soil.F

    r1516 r1524  
    55
    66      use comsoil_h, only: layer, mlayer, volcapa, inertiedat
    7       use comcstfi_mod, only: pi, daysec
     7      use comcstfi_mod, only: pi
     8      use time_phylmdz_mod, only: daysec
    89      use planete_mod, only: year_day
    910      use comgeomfi_h, only: long, lati
  • trunk/LMDZ.GENERIC/libf/phystd/tabfi.F

    r1482 r1524  
    5353      use planete_mod, only: year_day, periastr, apoastr, peri_day,
    5454     &                       obliquit, z0, lmixmin, emin_turb
    55       use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, dtphys,
    56      &                        daysec, r
     55      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
     56      use time_phylmdz_mod, only: dtphys, daysec
    5757      use callkeys_mod, only: check_cpp_match,force_cpp
    5858      implicit none
     
    507507      write(*,*)
    508508
    509       ENDIF                     !       of if (Lmodif == 1)
     509      ENDIF ! of if (Lmodif == 1)
    510510
    511511c-----------------------------------------------------------------------
  • trunk/LMDZ.GENERIC/libf/phystd/writediagfi.F

    r1422 r1524  
    4444     &                               is_master, gather
    4545      USE mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo
    46       USE temps_mod, ONLY: day_ini
     46      USE time_phylmdz_mod, ONLY: day_ini
    4747      implicit none
    4848
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecIR.F

    r1422 r1524  
    5050      use control_mod, only: ecritphy, iphysiq, day_step
    5151      use callkeys_mod, only: iradia
    52       USE temps_mod, ONLY: day_ini
     52      use time_phylmdz_mod, ONLY: day_ini
    5353
    5454      implicit none
  • trunk/LMDZ.GENERIC/libf/phystd/writediagspecVI.F

    r1422 r1524  
    5050      use control_mod, only: ecritphy, iphysiq, day_step
    5151      use callkeys_mod, only: iradia
    52       USE temps_mod, ONLY: day_ini
     52      use time_phylmdz_mod, ONLY: day_ini
    5353
    5454      implicit none
  • trunk/LMDZ.GENERIC/libf/phystd/writeg1d.F

    r1397 r1524  
    129129
    130130      SUBROUTINE endg1d(ngrid,nlayer,zlayer,ndt)
    131       USE comcstfi_mod, ONLY: dtphys, daysec
     131      USE time_phylmdz_mod, ONLY: dtphys, daysec
    132132      USE comg1d_mod, ONLY: g1d_nomfich,g1d_unitfich,g1d_nvar,
    133133     &  g1d_nomvar,g1d_titrevar,g1d_dimvar,g1d_nlayer,g1d_unitctl,
Note: See TracChangeset for help on using the changeset viewer.