Changeset 8ed5f11 in flexpart.git


Ignore:
Timestamp:
Apr 7, 2016, 8:55:43 AM (8 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
e31b3b5
Parents:
7e52e2e
Message:

Minor cosmetic changes

Location:
src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • src/ecmwf_mod.f90

    rdb712a8 r8ed5f11  
    2222!*******************************************************************************
    2323!   Include file for calculation of particle trajectories (Program FLEXPART)   *
    24 !        This file contains ECMWF specific parameters used in FLEXPART         *
    25 !        Note that module name differs from file name.                         *
    26 !        The makefile selects either this file, or gfs_mod.f90, depending      *
    27 !        on target.                                                            *
    2824!                                                                              *
    29 !        Author: ESO                                                           *
     25!       This file contains ECMWF specific parameters used in FLEXPART          *
     26!       Note that module name differs from file name.                          *
     27!       The makefile selects either this file, or gfs_mod.f90, depending       *
     28!       on target.                                                             *
    3029!                                                                              *
    31 !        2015                                                                  *
     30!       Author: ESO                                                            *
     31!                                                                              *
     32!       2015                                                                   *
    3233!                                                                              *
    3334!*******************************************************************************
     
    4445  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138 !ECMWF new
    4546  integer,parameter :: nxshift=359
    46 !  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138 !test BUG
    4747!  integer,parameter :: nxshift=0
    4848
    49 !
    5049  !*********************************************
    5150  ! Maximum dimensions of the nested input grids
     
    5554!  integer,parameter :: maxnests=1,nxmaxn=86,nymaxn=31
    5655
     56  ! nxmax,nymax        maximum dimension of wind fields in x and y
     57  !                    direction, respectively
     58  ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
     59  !                    direction (for fields on eta levels)
     60  ! nzmax              maximum dimension of wind fields in z direction
     61  !                    for the transformed Cartesian coordinates
     62  ! nxshift            for global grids (in x), the grid can be shifted by
     63  !                    nxshift grid points, in order to accomodate nested
     64  !                    grids, and output grids overlapping the domain "boundary"
     65  !                    nxshift must not be negative; "normal" setting would be 0
    5766
    5867end module wind_mod
  • src/gfs_mod.f90

    rb0434e1 r8ed5f11  
    2222!*******************************************************************************
    2323!   Include file for calculation of particle trajectories (Program FLEXPART)   *
    24 !        This file contains GFS specific parameters used in FLEXPART           *
    25 !        Note that module name differs from file name.                         *
    26 !        The makefile selects either this file, or ecmwf_mod.f90, depending    *
    27 !        on target.                                                            *
    2824!                                                                              *
    29 !        Author: ESO                                                           *
     25!       This file contains GFS specific parameters used in FLEXPART            *
     26!       Note that module name differs from file name.                          *
     27!       The makefile selects either this file, or ecmwf_mod.f90, depending     *
     28!       on target.                                                             *
    3029!                                                                              *
    31 !        2015                                                                  *
     30!       Author: ESO                                                            *
     31!                                                                              *
     32!       2015                                                                   *
    3233!                                                                              *
    3334!*******************************************************************************
     
    4445  integer,parameter :: nxshift=0     ! for GFS or FNL
    4546
     47  !*********************************************
     48  ! Maximum dimensions of the nested input grids
     49  !*********************************************
     50
    4651  integer,parameter :: maxnests=1,nxmaxn=361,nymaxn=181
     52
     53  ! nxmax,nymax        maximum dimension of wind fields in x and y
     54  !                    direction, respectively
     55  ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
     56  !                    direction (for fields on eta levels)
     57  ! nzmax              maximum dimension of wind fields in z direction
     58  !                    for the transformed Cartesian coordinates
     59  ! nxshift            for global grids (in x), the grid can be shifted by
     60  !                    nxshift grid points, in order to accomodate nested
     61  !                    grids, and output grids overlapping the domain "boundary"
     62  !                    nxshift must not be negative; "normal" setting would be 0
    4763end module wind_mod
  • src/mpi_mod.f90

    r1c3c778 r8ed5f11  
    195195    if (dep_prec==dp) then
    196196      mp_cp = MPI_REAL8
    197       if (lroot) write(*,*) 'Using double precision for deposition fields'
     197      ! TODO: write info message for serial version as well
     198      if (lroot.and.verbosity>0) write(*,*) 'Using double precision for deposition fields'
    198199    else if (dep_prec==sp) then
    199200      mp_cp = MPI_REAL4
    200       if (lroot) write(*,*) 'Using single precision for deposition fields'
     201      if (lroot.and.verbosity>0) write(*,*) 'Using single precision for deposition fields'
    201202    else
    202203      write(*,*) 'ERROR: something went wrong setting MPI real precision'
  • src/par_mod.f90

    r1c3c778 r8ed5f11  
    2828!        1997                                                                  *
    2929!                                                                              *
    30 !        Last update 15 August 2013 IP                                         *
     30!        Update 15 August 2013 IP                                              *
     31!                                                                              *
     32!        ESO 2016:                                                             *
     33!          GFS specific parameters moved to gfs_mod.f90                        *
     34!          ECMWF specific parameters moved to ecmwf_mod.f90                    *
    3135!                                                                              *
    3236!*******************************************************************************
     
    3438module par_mod
    3539
     40!************************************************************************
    3641! wind_mod: is gfs_mod.f90 for target gfs, ecmwf_mod.f90 for target ecmwf
    3742!************************************************************************
     
    135140  !*********************************************
    136141 
    137   ! nxmax,nymax,nuvzmax,nwzmax,nzmax:
    138   ! Moved to ecmwf.f90 (for ECMWF) / gfs.f90 (GFS)
     142  ! Moved to ecmwf_mod.f90 (for ECMWF) / gfs_mod.f90 (for GFS)
    139143 
    140 
    141   !integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !FNL XF
    142   !integer,parameter :: nxmax=361,nymax=181,nuvzmax=152,nwzmax=152,nzmax=152 !ECMWF new
    143   !integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !ECMWF
    144   !integer,parameter :: nxmax=721,nymax=361,nuvzmax=64,nwzmax=64,nzmax=64
    145 
    146 !  integer,parameter :: nxshift=359 ! for ECMWF
    147   !integer,parameter :: nxshift=0     ! for GFS or FNL
    148 
    149144  integer,parameter :: nconvlevmax = nuvzmax-1
    150145  integer,parameter :: na = nconvlevmax+1
    151 
    152   ! moved to gfs_mod.f90 / ecmwf_mod.f90
    153   !
    154   ! nxmax,nymax        maximum dimension of wind fields in x and y
    155   !                    direction, respectively
    156   ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
    157   !                    direction (for fields on eta levels)
    158   ! nzmax              maximum dimension of wind fields in z direction
    159   !                    for the transformed Cartesian coordinates
    160   ! nxshift            for global grids (in x), the grid can be shifted by
    161   !                    nxshift grid points, in order to accomodate nested
    162   !                    grids, and output grids overlapping the domain "boundary"
    163   !                    nxshift must not be negative; "normal" setting would be 0
    164146
    165147  ! ntracermax         maximum number of tracer species in convection
    166148  ! nconvlevmax        maximum number of levels for convection
    167149  ! na                 parameter used in Emanuel's convect subroutine
    168 
    169 
    170   !*********************************************
    171   ! Maximum dimensions of the nested input grids
    172   !*********************************************
    173 
    174   !integer,parameter :: maxnests=0, nxmaxn=0, nymaxn=0
    175   !integer,parameter :: maxnests=0,nxmaxn=351,nymaxn=351 !ECMWF
    176 
    177   !integer,parameter :: maxnests=1, nxmaxn=201, nymaxn=161 ! FNL XF
    178   ! maxnests                maximum number of nested grids
    179   ! nxmaxn,nymaxn           maximum dimension of nested wind fields in
    180   !                         x and y direction, respectively
    181150
    182151
     
    217186  !**************************************************
    218187
    219   integer,parameter :: maxpart=40000000
     188  integer,parameter :: maxpart=10000
    220189  integer,parameter :: maxspec=1
    221190  real,parameter :: minmass=0.0001
  • src/timemanager_mpi.f90

    r7e52e2e r8ed5f11  
    228228    if (mp_measure_time.and..not.(lmpreader.and.lmp_use_reader)) call mpif_mtime('getfields',0)
    229229
     230! Two approaches to MPI getfields is implemented:
    230231! Version 1 (lmp_sync=.true.) uses a read-ahead process where send/recv is done
    231232! in sync at start of each new field time interval
     233!
     234! Version 2 (lmp_sync=.false.) is for holding three fields in memory. Uses a
     235! read-ahead process where sending/receiving of the 3rd fields is done in
     236! the background in parallel with performing computations with fields 1&2
     237!********************************************************************************
     238
    232239    if (lmp_sync.and.lmp_use_reader.and.memstat.gt.0) then
    233240      call mpif_gf_send_vars(memstat)
    234241      if (numbnests>0) call mpif_gf_send_vars_nest(memstat)
    235 ! Version 2  (lmp_sync=.false., see below) is also used whenever 2 new fields are
     242! Version 2  (lmp_sync=.false.) is also used whenever 2 new fields are
    236243! read (as at first time step), in which case async send/recv is impossible.
    237244    else if (.not.lmp_sync.and.lmp_use_reader.and.memstat.ge.32) then
     
    240247    end if
    241248
    242 ! Version 2 (lmp_sync=.false.) is for holding three fields in memory. Uses a
    243 ! read-ahead process where sending/receiving of the 3rd fields is done in
    244 ! the background in parallel with performing computations with fields 1&2
    245 !********************************************************************************
    246249    if (.not.lmp_sync) then
    247250   
    248 ! READER PROCESS:
     251! Reader process:
    249252      if (memstat.gt.0..and.memstat.lt.32.and.lmp_use_reader.and.lmpreader) then
    250253        if (mp_dev_mode) write(*,*) 'Reader process: calling mpif_gf_send_vars_async'
     
    252255      end if
    253256
    254 ! COMPLETION CHECK:
     257! Completion check:
    255258! Issued at start of each new field period.
    256259      if (memstat.ne.0.and.memstat.lt.32.and.lmp_use_reader) then
     
    258261      end if
    259262
    260 ! RECVEIVING PROCESS(ES):
    261       ! eso TODO: at this point we do not know if clwc/ciwc will be available
    262       ! at next time step. Issue receive request anyway, cancel at mpif_gf_request
     263! Recveiving process(es):
     264! eso TODO: at this point we do not know if clwc/ciwc will be available
     265! at next time step. Issue receive request anyway, cancel at mpif_gf_request
    263266      if (memstat.gt.0.and.lmp_use_reader.and..not.lmpreader) then
    264267        if (mp_dev_mode) write(*,*) 'Receiving process: calling mpif_gf_send_vars_async. PID: ', mp_pid
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG