Changeset c0884a8 in flexpart.git for src/FLEXPART_MPI.f90


Ignore:
Timestamp:
Jul 20, 2018, 2:40:39 PM (6 years ago)
Author:
pesei <petra seibert at univie ac at>
Branches:
univie
Children:
7ca2ef4
Parents:
f251e57
Message:

replace CTBTO code for checking type of GRIB

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART_MPI.f90

    r20963b1 rc0884a8  
    4040  !       detected metdata format                                              *
    4141  !     - Passed metdata format down to timemanager                            *
     42  !                                                                            *
     43  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     44  !                                                                            *
    4245  !*****************************************************************************
    4346  !                                                                            *
     
    5457  use mpi_mod
    5558  use random_mod, only: gasdev1
    56   use class_gribfile
     59  use check_gribfile_mod
    5760
    5861#ifdef USE_NCF
     
    6265  implicit none
    6366
    64   integer :: i,j,ix,jy,inest
     67  integer :: i,j,ix,jy,inest,id_centre
    6568  integer :: idummy = -320
    6669  character(len=256) :: inline_options  !pathfile, flexversion, arg2
    67   integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
    68   integer :: detectformat
    6970  integer(selected_int_kind(16)), dimension(maxspec) :: tot_b=0, &
    7071       & tot_i=0
     
    203204  ! Detect metdata format
    204205  !**********************
    205 
    206   metdata_format = detectformat()
    207 
    208   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     206  call cg_get_centre(path(3)(1:length(3)) // trim(wfname(1)), id_centre)
     207  if (id_centre.eq.icg_id_ecmwf) then
    209208    if (lroot) print *,'ECMWF metdata detected'
    210   elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    211     if (lroot) print *,'NCEP metdata detected'
     209  elseif (id_centre.eq.icg_id_ncep) then
     210    if (lroot) print *,'NCEP met data detected'
    212211  else
    213     if (lroot) print *,'Unknown metdata format'
     212    if (lroot) print *,'Unknown met data format'
    214213    stop
    215214  endif
     
    233232  endif
    234233
    235   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     234  if (id_centre.eq.icg_id_ecmwf) then
    236235    call gridcheck_ecmwf
    237236  else
     
    480479
    481480
    482   call timemanager(metdata_format)
     481  call timemanager(id_centre)
    483482
    484483
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG