Changeset 1969


Ignore:
Timestamp:
Jul 11, 2018, 11:47:54 AM (6 years ago)
Author:
emillour
Message:

Mars GCM:
Some cosmetic changes:

  • make watercloud less verbose
  • turn vdifc.F into a module
  • turn updatereffrad.F into a module

EM

Location:
trunk/LMDZ.MARS
Files:
4 edited
2 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1963 r1969  
    26032603== 05/07/2018 == MV
    26042604- improvedclouds.F changed to module improvedclouds_mod.F
     2605
     2606== 11/07/2018 == EM
     2607Some cosmetic changes:
     2608- make watercloud less verbose
     2609- turn vdifc.F into a module
     2610- turn updatereffrad.F into a module
  • trunk/LMDZ.MARS/libf/phymars/callradite_mod.F

    r1918 r1969  
    1212
    1313      use aeropacity_mod, only: aeropacity
     14      use updatereffrad_mod, only: updatereffrad
    1415      use dimradmars_mod, only: ndomainsz, nflev, nsun, nir
    1516      use dimradmars_mod, only: naerkind, name_iaer,
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1962 r1969  
    5050      USE comcstfi_h, only: r, cpp, mugaz, g, rcp, pi, rad
    5151      USE calldrag_noro_mod, ONLY: calldrag_noro
     52      USE vdifc_mod, ONLY: vdifc
    5253      use param_v4_h, only: nreact,n_avog,
    5354     &                      fill_data_thermos, allocate_param_thermos
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad_mod.F

    r1968 r1969  
     1      MODULE updatereffrad_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE updatereffrad(ngrid,nlayer,
    28     &                rdust,rice,nuice,
    39     &                reffrad,nueffrad,
    410     &                pq,tauscaling,tau,pplay)
    5        USE updaterad
     11       USE updaterad, ONLY: updaterdust, updaterice_micro,
     12     &                      updaterice_typ
    613       use tracer_mod, only: nqmx, igcm_dust_mass, igcm_dust_number,
    714     &                       igcm_h2o_ice, igcm_ccn_mass, radius,
     
    1219     &            iaer_dust_conrath,iaer_dust_doubleq,
    1320     &            iaer_dust_submicron,iaer_h2o_ice
    14        USE comcstfi_h
     21
    1522       IMPLICIT NONE
    1623c=======================================================================
     
    3542c    -------------
    3643c
    37 #include "callkeys.h"
     44      include "callkeys.h"
    3845
    3946c-----------------------------------------------------------------------
     
    202209      ENDDO ! iaer (loop on aerosol kind)
    203210
    204       RETURN
    205       END
     211      END SUBROUTINE updatereffrad
     212     
     213      END MODULE updatereffrad_mod
  • trunk/LMDZ.MARS/libf/phymars/vdifc_mod.F

    r1968 r1969  
     1      MODULE vdifc_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE vdifc(ngrid,nlay,nq,co2ice,ppopsk,
    28     $                ptimestep,pcapcal,lecrit,
     
    1218     &                      igcm_h2o_ice, alpha_lift
    1319      use surfdat_h, only: watercaptag, frost_albedo_threshold, dryness
    14       USE comcstfi_h
     20      USE comcstfi_h, ONLY: cpp, r, rcp, g
    1521      use turb_mod, only: turb_resolved, ustar, tstar
    1622      IMPLICIT NONE
     
    872878      ENDIF
    873879
    874       RETURN
    875880      END SUBROUTINE vdifc
     881
     882      END MODULE vdifc_mod
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r1964 r1969  
    8888      ! for time loop
    8989      INTEGER microstep  ! time subsampling step variable
    90       INTEGER imicro     ! time subsampling for coupled water microphysics & sedimentation
    91       SAVE imicro
    92       REAL microtimestep ! integration timestep for coupled water microphysics & sedimentation
    93       SAVE microtimestep
     90      INTEGER,SAVE :: imicro ! time subsampling for coupled water microphysics & sedimentation
     91      REAL,SAVE :: microtimestep ! integration timestep for coupled water microphysics & sedimentation
     92      REAL,SAVE :: microtimestep_prev=-999
    9493     
    9594      ! tendency given by clouds (inside the micro loop)
     
    145144#endif
    146145        call getin("imicro",imicro)
    147         write(*,*)"imicro = ",imicro
     146        write(*,*)"watercloud: imicro = ",imicro
    148147       
    149148        firstcall=.false.
     
    153152      !!     TBD: consider possible diff imicro with domains?
    154153      microtimestep = ptimestep/real(imicro)
    155       write(*,*)"Physical timestep is",ptimestep
    156       write(*,*)"Microphysics timestep is",microtimestep
    157 
     154      if (microtimestep/=microtimestep_prev) then
     155        ! only tell the world if microtimestep has changed
     156        write(*,*)"watercloud: Physical timestep is ",ptimestep
     157        write(*,*)"watercloud: Microphysics timestep is ",microtimestep
     158        microtimestep_prev=microtimestep
     159      endif
    158160     
    159161c-----Initialization
Note: See TracChangeset for help on using the changeset viewer.