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


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART_MPI.f90

    r0c00f1f r20963b1  
    5353  use conv_mod
    5454  use mpi_mod
    55   use netcdf_output_mod, only: writeheader_netcdf
    5655  use random_mod, only: gasdev1
    5756  use class_gribfile
     57
     58#ifdef USE_NCF
     59  use netcdf_output_mod, only: writeheader_netcdf
     60#endif
    5861
    5962  implicit none
     
    6467  integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
    6568  integer :: detectformat
    66 
     69  integer(selected_int_kind(16)), dimension(maxspec) :: tot_b=0, &
     70       & tot_i=0
    6771
    6872
     
    203207
    204208  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    205     print *,'ECMWF metdata detected'
     209    if (lroot) print *,'ECMWF metdata detected'
    206210  elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    207     print *,'NCEP metdata detected'
     211    if (lroot) print *,'NCEP metdata detected'
    208212  else
    209     print *,'Unknown metdata format'
     213    if (lroot) print *,'Unknown metdata format'
    210214    stop
    211215  endif
     
    378382
    379383  if (mp_measure_time) call mpif_mtime('iotime',0)
     384
    380385  if (lroot) then ! MPI: this part root process only
    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 !
     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
    397402    if (verbosity.gt.0) then
    398403      print*,'call writeheader'
     
    402407! FLEXPART 9.2 ticket ?? write header in ASCII format
    403408    call writeheader_txt
    404 !if (nested_output.eq.1) call writeheader_nest
     409
    405410    if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
    406411    if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
     
    409414
    410415  if (mp_measure_time) call mpif_mtime('iotime',0)
    411 
    412   !open(unitdates,file=path(2)(1:length(2))//'dates')
    413416
    414417  if (verbosity.gt.0 .and. lroot) then
     
    481484
    482485! NIK 16.02.2005
    483   if (lroot) then
    484     call MPI_Reduce(MPI_IN_PLACE, tot_blc_count, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     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, &
    485488         & mp_comm_used, mp_ierr)
    486     call MPI_Reduce(MPI_IN_PLACE, tot_inc_count, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
     489    call MPI_Reduce(tot_inc_count, tot_i, nspec, MPI_INTEGER8, MPI_SUM, id_root, &
    487490         & 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
    495491  end if
     492 
    496493
    497494  if (lroot) then
     
    500497      write(*,*) 'Scavenging statistics for species ', species(i), ':'
    501498      write(*,*) 'Total number of occurences of below-cloud scavenging', &
    502            & tot_blc_count(i)
     499           & tot_b(i)
     500!           & tot_blc_count(i)
    503501      write(*,*) 'Total number of occurences of in-cloud    scavenging', &
    504            & tot_inc_count(i)
     502           & tot_i(i)
     503!           & tot_inc_count(i)
    505504      write(*,*) '**********************************************'
    506505    end do
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG