Changeset 2563


Ignore:
Timestamp:
Sep 21, 2021, 1:55:55 PM (3 years ago)
Author:
emillour
Message:

Mars GCM:
Improve wstats: the callstats flag is now embedded within wstats and checked
internaly so no need to have some "if (callstats)" conditions around calls
to wstats anymore.
In addition: wstats now looks for an (optional) stats.def file in the
directory where the GCM is run to know which variable should be included
in the stats.nc file. The stats.def ASCII file should simply contain
one variable name per line, in the same way as the diagfi.def file for
diagfi outputs. If there is no stats.def file then all variables sent to
wstats will be in the stats.nc file (which matches the behaviour prior to
this improvement).
EM

Location:
trunk/LMDZ.MARS
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2562 r2563  
    34463446== 07/09/2021 == EM
    34473447Some code cleanup and refactoring around wstats:
    3448 - turn wstats.F90�in a module
     3448- turn wstats.F90 into a module
    34493449- remove no useless statto_mod.F90
    34503450- incorporate auxilliary inistats and mkstats routines in wstats_mod.F90
     
    34653465 - add tracers ccnco2_h2o_mass_ice, ccnco2_h2o_mass_ccn, ccnco2_h2o_number in place of mem_Nccn_co2, mem_Qccn_co2
    34663466 - modification of updaterice_microco2 to take into account water ice as CN and not only dust as CN
     3467 
     3468== 20/09/2021 == EM
     3469Improve wstats: the callstats flag is now embedded within wstats and checked
     3470internaly so no need to have some "if (callstats)" conditions around calls
     3471to wstats anymore.
     3472In addition: wstats now looks for an (optional) stats.def file in the
     3473directory where the GCM is run to know which variable should be included
     3474in the stats.nc file. The stats.def ASCII file should simply contain
     3475one variable name per line, in the same way as the diagfi.def file for
     3476diagfi outputs. If there is no stats.def file then all variables sent to
     3477wstats will be in the stats.nc file (which matches the behaviour prior to
     3478this improvement).
  • trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90

    r2559 r2563  
    3131      use photolysis_mod, only: init_photolysis, nphot
    3232      use iono_h, only: temp_elect
    33       use wstats_mod, only: callstats, wstats
     33      use wstats_mod, only: wstats
    3434
    3535      implicit none
     
    953953!            endif
    954954           
    955             if (callstats) then
    956955               call wstats(ngrid,'jo3','j o3->o1d',       &
    957956                           's-1',3,jo3_3d(1,1))
     
    962961               call wstats(ngrid,'mmean','mean molecular mass',       &
    963962                           'g.mole-1',3,mmean(1,1))
    964             endif
    965963         end if ! of if (ngrid.gt.1)
    966964      end if ! of if (output)
  • trunk/LMDZ.MARS/libf/aeronomars/surfacearea.F

    r2559 r2563  
    99      use conc_mod, only: rnew
    1010      use comcstfi_h, only: pi
    11       use wstats_mod, only: callstats, wstats
     11      use wstats_mod, only: wstats
    1212      implicit none
    1313
     
    114114! write diagnostics in micron2/cm3
    115115     
    116       if (callstats) then
    117         call wstats(ngrid,"surfdust", "Dust surface area",
     116      call wstats(ngrid,"surfdust", "Dust surface area",
    118117     $            "micron2 cm-3",3,surfdust*1.e6)
    119         call wstats(ngrid,"surfice", "Ice cloud surface area",
     118      call wstats(ngrid,"surfice", "Ice cloud surface area",
    120119     $            "micron2 cm-3",3,surfice*1.e6)
    121       endif
     120
    122121      call writediagfi(ngrid,"surfdust", "Dust surface area",
    123122     $            "micron2 cm-3",3,surfdust*1.e6)
     
    125124     $            "micron2 cm-3",3,surfice*1.e6)
    126125
    127       return
    128126      end
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2562 r2563  
    26022602c        WSTATS: Saving statistics
    26032603c        -----------------------------------------------------------------
    2604 c        ("stats" stores and accumulates 8 key variables in file "stats.nc"
     2604c        ("stats" stores and accumulates key variables in file "stats.nc"
    26052605c        which can later be used to make the statistic files of the run:
    2606 c        "stats")          only possible in 3D runs !
     2606c        if flag "callstats" from callphys.def is .true.)
    26072607         
    2608        IF (callstats) THEN
    2609 
    26102608        call wstats(ngrid,"ps","Surface pressure","Pa",2,ps)
    26112609        call wstats(ngrid,"tsurf","Surface temperature","K",2,tsurf)
     
    28582856           end if ! of if (tracer)
    28592857
    2860            IF(lastcall) THEN
     2858           IF(lastcall.and.callstats) THEN
    28612859             write (*,*) "Writing stats..."
    28622860             call mkstats(ierr)
    28632861           ENDIF
    28642862
    2865          ENDIF !if callstats
    28662863
    28672864c        (Store EOF for Mars Climate database software)
  • trunk/LMDZ.MARS/libf/phymars/wstats_mod.F90

    r2559 r2563  
    2828use mod_phys_lmdz_para, only : is_mpi_root, is_master, gather, klon_mpi_begin
    2929use mod_grid_phy_lmdz, only : klon_glo, Grid1Dto2D_glo, &
    30                               nbp_lon, nbp_lat, nbp_lev
     30                              nbp_lon, nbp_lat, nbp_lev, &
     31                              grid_type, unstructured
    3132implicit none
    3233
     
    4647integer, dimension(4)  :: id,start,sizes
    4748logical, save :: firstcall=.TRUE.
    48 integer :: l,i,j,ig0
    4949integer,save :: indx
    50 
    5150integer, save :: step=0
    5251!$OMP THREADPRIVATE(firstcall,indx,step)
     52integer :: l,i,j,ig0,n
     53
     54! Added to read an optional stats.def file to select outputs
     55logical,save :: stats_def ! .true. if there is a stats.def file
     56integer,save :: n_name_def ! number of fields to output in stats.nc
     57! NB: stats_def and n_name_def do not need be threadprivate
     58integer,parameter :: n_name_def_max=199 ! max number of fields to output
     59character(len=120),save :: name_def(n_name_def_max)
     60logical :: getout ! to trigger an early exit if variable not in output list
    5361
    5462! Added to work in parallel mode
     
    6876#endif
    6977
     78! 0. Preliminary stuff
     79if (callstats.eqv..false.) then
     80  ! exit because creating/writing stats.nc not requested by user
     81  return
     82endif
     83
     84if (grid_type==unstructured) then
     85  ! exit because non-structured grid case is not handled
     86  return
     87endif
     88
    7089! 1. Initialization (creation of stats.nc file)
    7190if (firstcall) then
    7291   firstcall=.false.
     92
     93!$OMP MASTER
     94  ! open stats.def definition file if there is one
     95  open(99,file="stats.def",status='old',form='formatted',&
     96       iostat=ierr)
     97  if (ierr.eq.0) then
     98    stats_def=.true. ! yes there is a stats.def file
     99    write(*,*) "*****************"
     100    write(*,*) "Reading stats.def"
     101    write(*,*) "*****************"
     102    do n=1,n_name_def_max
     103      read(99,fmt='(a)',end=88) name_def(n)
     104      write(*,*) 'Output in stats: ', trim(name_def(n))
     105    enddo
     10688  continue
     107    ! check there is no overflow
     108    if (n.ge.n_name_def_max) then
     109      write(*,*) "n_name_def_max too small in wstats:",n
     110      call abort_physic("wstats","n_name_def_max too small",1)
     111    endif
     112    n_name_def=n-1
     113    close(99)
     114  else
     115    stats_def=.false. ! no stats.def file; output all fields sent to wstats
     116  endif ! of if (ierr.eq.0)
     117!$OMP END MASTER
     118!$OMP BARRIER
     119
    73120   firstvar=trim((nom))
    74121   call inistats(ierr)
     
    88135     allocate(dx2(1,1))
    89136   endif
    90 endif
     137endif ! of if (firstcall)
    91138
    92139if (firstvar==nom) then ! If we're back to the first variable, increment time counter
     
    98145   RETURN
    99146endif
     147
     148! Exit if there is a stats.def file and the variable is not in the list
     149if (stats_def) then
     150  getout=.true.
     151  do n=1,n_name_def
     152    ! look for the variable's name in the list
     153    if (trim(name_def(n)).eq.nom) then
     154      getout=.false.
     155      ! found it, no need to scan the rest of the list exit loop
     156      exit
     157    endif
     158  enddo
     159  if (getout) then
     160    ! variable not in the list so exit routine now
     161    return
     162  endif
     163endif ! of if (stats_def)
    100164
    101165! collect fields on a global physics grid
Note: See TracChangeset for help on using the changeset viewer.