Changes in src/FLEXPART_MPI.f90 [20963b1:0c00f1f] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART_MPI.f90

    r20963b1 r0c00f1f  
    5353  use conv_mod
    5454  use mpi_mod
     55  use netcdf_output_mod, only: writeheader_netcdf
    5556  use random_mod, only: gasdev1
    5657  use class_gribfile
    57 
    58 #ifdef USE_NCF
    59   use netcdf_output_mod, only: writeheader_netcdf
    60 #endif
    6158
    6259  implicit none
     
    6764  integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
    6865  integer :: detectformat
    69   integer(selected_int_kind(16)), dimension(maxspec) :: tot_b=0, &
    70        & tot_i=0
     66
    7167
    7268
     
    207203
    208204  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    209     if (lroot) print *,'ECMWF metdata detected'
     205    print *,'ECMWF metdata detected'
    210206  elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    211     if (lroot) print *,'NCEP metdata detected'
     207    print *,'NCEP metdata detected'
    212208  else
    213     if (lroot) print *,'Unknown metdata format'
     209    print *,'Unknown metdata format'
    214210    stop
    215211  endif
     
    382378
    383379  if (mp_measure_time) call mpif_mtime('iotime',0)
    384 
    385380  if (lroot) then ! MPI: this part root process only
    386 #ifdef USE_NCF
    387     if (lnetcdfout.eq.1) then
    388       call writeheader_netcdf(lnest=.false.)
    389     else
    390       call writeheader
    391     end if
    392    
    393     if (nested_output.eq.1) then
    394       if (lnetcdfout.eq.1) then
    395         call writeheader_netcdf(lnest=.true.)
    396       else
    397         call writeheader_nest
    398       endif
    399     endif
    400 #endif
    401 
     381
     382  if (lnetcdfout.eq.1) then
     383    call writeheader_netcdf(lnest=.false.)
     384  else
     385    call writeheader
     386  end if
     387
     388  if (nested_output.eq.1) then
     389    if (lnetcdfout.eq.1) then
     390      call writeheader_netcdf(lnest=.true.)
     391    else
     392      call writeheader_nest
     393    endif
     394  endif
     395
     396!
    402397    if (verbosity.gt.0) then
    403398      print*,'call writeheader'
     
    407402! FLEXPART 9.2 ticket ?? write header in ASCII format
    408403    call writeheader_txt
    409 
     404!if (nested_output.eq.1) call writeheader_nest
    410405    if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
    411406    if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
     
    414409
    415410  if (mp_measure_time) call mpif_mtime('iotime',0)
     411
     412  !open(unitdates,file=path(2)(1:length(2))//'dates')
    416413
    417414  if (verbosity.gt.0 .and. lroot) then
     
    484481
    485482! NIK 16.02.2005
    486   if (mp_partgroup_pid.ge.0) then ! Skip for readwind process
    487     call MPI_Reduce(tot_blc_count, tot_b, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     483  if (lroot) then
     484    call MPI_Reduce(MPI_IN_PLACE, tot_blc_count, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
    488485         & mp_comm_used, mp_ierr)
    489     call MPI_Reduce(tot_inc_count, tot_i, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     486    call MPI_Reduce(MPI_IN_PLACE, tot_inc_count, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
    490487         & mp_comm_used, mp_ierr)
     488  else
     489    if (mp_partgroup_pid.ge.0) then ! Skip for readwind process
     490      call MPI_Reduce(tot_blc_count, 0, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     491           & mp_comm_used, mp_ierr)
     492      call MPI_Reduce(tot_inc_count, 0, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     493           & mp_comm_used, mp_ierr)
     494    end if
    491495  end if
    492  
    493496
    494497  if (lroot) then
     
    497500      write(*,*) 'Scavenging statistics for species ', species(i), ':'
    498501      write(*,*) 'Total number of occurences of below-cloud scavenging', &
    499            & tot_b(i)
    500 !           & tot_blc_count(i)
     502           & tot_blc_count(i)
    501503      write(*,*) 'Total number of occurences of in-cloud    scavenging', &
    502            & tot_i(i)
    503 !           & tot_inc_count(i)
     504           & tot_inc_count(i)
    504505      write(*,*) '**********************************************'
    505506    end do
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG