Changeset c0884a8 in flexpart.git


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

Files:
1 added
2 deleted
20 edited

Legend:

Unmodified
Added
Removed
  • documentation/fluxdiagram.txt

    • Property mode changed from 100755 to 100644
  • documentation/memo_verttr.ps.gz

    • Property mode changed from 100755 to 100644
  • documentation/program_list.txt

    • Property mode changed from 100755 to 100644
  • options/COMMAND.namelist

    • Property mode changed from 100755 to 100644
  • options/COMMAND.oldformat

    • Property mode changed from 100755 to 100644
  • src/FLEXPART.f90

    r77778f8 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
    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
    69 
    7070
    7171
     
    190190  ! Detect metdata format
    191191  !**********************
    192 
    193   metdata_format = detectformat()
    194 
    195   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    196     print *,'ECMWF metdata detected'
    197   elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    198     print *,'NCEP metdata detected'
     192 
     193  call cg_get_centre(path(3)(1:length(3)) // trim(wfname(1)), id_centre)
     194  if (id_centre.eq.icg_id_ecmwf) then
     195    print *,'ECMWF met data detected'
     196  elseif (id_centre.eq.icg_id_ncep) then
     197    print *,'NCEP met data detected'
    199198  else
    200     print *,'Unknown metdata format'
     199    print *,'Unknown met data format'
    201200    stop
    202201  endif
     
    220219  endif
    221220
    222   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     221  if (id_centre.eq.icg_id_ecmwf) then
    223222    call gridcheck_ecmwf
    224223  else
     
    449448  endif
    450449
    451   call timemanager(metdata_format)
     450  call timemanager(id_centre)
    452451
    453452! NIK 16.02.2005
  • 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
  • src/calcmatrix.f90

    rd8eed02 rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine calcmatrix(lconv,delt,cbmf,metdata_format)
     22subroutine calcmatrix(lconv,delt,cbmf,id_centre)
    2323  !                        o    i    o
    2424  !*****************************************************************************
     
    4040  !     - Merged calcmatrix and calcmatrix_gfs into one routine using if-then  *
    4141  !       for meteo-type dependent code                                        *
     42  !                                                                            *
     43  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     44  !                                                                            *
    4245  !*****************************************************************************
    4346  !                                                                            *
     
    4548  !  delt         time step for convection [s]                                 *
    4649  !  cbmf         cloud base mass flux                                         *
    47   !  metdata_format format of metdata (ecmwf/gfs)                              *
     50  !  id_centre    format of metdata (ecmwf/gfs)                                *
    4851  !                                                                            *
    4952  !*****************************************************************************
     
    5255  use com_mod
    5356  use conv_mod
    54   use class_gribfile
     57  use check_gribfile_mod
    5558
    5659  implicit none
    5760
    5861  real :: rlevmass,summe
    59   integer :: metdata_format
     62  integer :: id_centre
    6063
    6164  integer :: iflag, k, kk, kuvz
     
    8891  do kuvz = 2,nuvz
    8992    k = kuvz-1
    90     if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     93    if (id_centre.eq.icg_id_ecmwf) then
    9194    pconv(k) = (akz(kuvz) + bkz(kuvz)*psconv)
    9295    phconv(kuvz) = (akm(kuvz) + bkm(kuvz)*psconv)
  • src/calcpar.f90

    r027e844 rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine calcpar(n,uuh,vvh,pvh,metdata_format)
     22subroutine calcpar(n,uuh,vvh,pvh,id_centre)
    2323  !                   i  i   i   o
    2424  !*****************************************************************************
     
    4646  !     - Merged calcpar and calcpar_gfs into one routine using if-then        *
    4747  !       for meteo-type dependent code                                        *
    48   !*****************************************************************************
    49 
     48  !                                                                            *
     49  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     50  !                                                                            *
    5051  !*****************************************************************************
    5152  !                                                                            *
     
    5556  ! vvh                                                                        *
    5657  ! pvh                                                                        *
    57   ! metdata_format     format of metdata (ecmwf/gfs)                           *
     58  ! id_centre          format of metdata (ecmwf/gfs)                           *
    5859  !                                                                            *
    5960  ! Constants:                                                                 *
     
    6869  use par_mod
    6970  use com_mod
    70   use class_gribfile
     71  use check_gribfile_mod
    7172
    7273  implicit none
    7374
    74   integer :: metdata_format
     75  integer :: id_centre
    7576  integer :: n,ix,jy,i,kz,lz,kzmin,llev,loop_start
    7677  real :: ttlev(nuvzmax),qvlev(nuvzmax),obukhov,scalev,ol,hmixplus
     
    125126  !***********************************************
    126127
    127       if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
     128      if (id_centre.eq.icg_id_ncep) then
    128129        ! NCEP version: find first level above ground
    129130        llev = 0
     
    137138        ! calculate inverse Obukhov length scale with tth(llev)
    138139        ol=obukhov(ps(ix,jy,1,n),tt2(ix,jy,1,n),td2(ix,jy,1,n), &
    139              tth(ix,jy,llev,n),ustar(ix,jy,1,n),sshf(ix,jy,1,n),akm,bkm,akz(llev),metdata_format)
     140             tth(ix,jy,llev,n),ustar(ix,jy,1,n),sshf(ix,jy,1,n), &
     141             akm,bkm,akz(llev),id_centre)
    140142      else
    141143        llev=0
    142144        ol=obukhov(ps(ix,jy,1,n),tt2(ix,jy,1,n),td2(ix,jy,1,n), &
    143             tth(ix,jy,2,n),ustar(ix,jy,1,n),sshf(ix,jy,1,n),akm,bkm,akzdummy,metdata_format)
     145            tth(ix,jy,2,n),ustar(ix,jy,1,n),sshf(ix,jy,1,n), &
     146            akm,bkm,akzdummy,id_centre)
    144147      end if
    145148
     
    161164      end do
    162165
    163       if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
     166      if (id_centre.eq.icg_id_ncep) then
    164167        ! NCEP version hmix has been read in in readwind.f, is therefore not calculated here
    165168      call richardson(ps(ix,jy,1,n),ustar(ix,jy,1,n),ttlev,qvlev, &
    166169           ulev,vlev,nuvz,akz,bkz,sshf(ix,jy,1,n),tt2(ix,jy,1,n), &
    167              td2(ix,jy,1,n),hmixdummy,wstar(ix,jy,1,n),hmixplus,metdata_format)
     170             td2(ix,jy,1,n),hmixdummy,wstar(ix,jy,1,n),hmixplus,id_centre)
    168171      else
    169172        call richardson(ps(ix,jy,1,n),ustar(ix,jy,1,n),ttlev,qvlev, &
    170173             ulev,vlev,nuvz,akz,bkz,sshf(ix,jy,1,n),tt2(ix,jy,1,n), &
    171              td2(ix,jy,1,n),hmix(ix,jy,1,n),wstar(ix,jy,1,n),hmixplus,metdata_format)
     174             td2(ix,jy,1,n),hmix(ix,jy,1,n),wstar(ix,jy,1,n),hmixplus,id_centre)
    172175      end if
    173176
     
    218221      pold=ps(ix,jy,1,n)
    219222      zold=0.
    220       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     223      if (id_centre.eq.icg_id_ecmwf) then
    221224        loop_start=2
    222225      else
     
    242245  !************************************************************************
    243246
    244       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     247      if (id_centre.eq.icg_id_ecmwf) then
    245248        loop_start=1
    246249      else
  • src/calcpar_nests.f90

    r6ecb30a rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine calcpar_nests(n,uuhn,vvhn,pvhn,metdata_format)
     22subroutine calcpar_nests(n,uuhn,vvhn,pvhn,id_centre)
    2323  !                         i  i    i    o
    2424  !*****************************************************************************
     
    4444  !   Unified ECMWF and GFS builds                                             *
    4545  !   Marian Harustak, 12.5.2017                                               *
    46   !     - Added passing of metdata_format as it was needed by called routines  *
     46  !     - Added passing of id_centre as it was needed by called routines       *
     47  !                                                                            *
     48  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     49  !                                                                            *
    4750  !*****************************************************************************
    4851  !                                                                            *
    4952  ! Variables:                                                                 *
    5053  ! n                  temporal index for meteorological fields (1 to 3)       *
    51   ! metdata_format     format of metdata (ecmwf/gfs)                           *
     54  ! id_centre          format of metdata (ecmwf/gfs)                           *
    5255  !                                                                            *
    5356  ! Constants:                                                                 *
     
    6568  implicit none
    6669
    67   integer :: metdata_format
     70  integer :: id_centre
    6871  integer :: n,ix,jy,i,l,kz,lz,kzmin
    6972  real :: ttlev(nuvzmax),qvlev(nuvzmax),obukhov,scalev,ol,hmixplus,dummyakzllev
     
    116119      ol=obukhov(psn(ix,jy,1,n,l),tt2n(ix,jy,1,n,l), &
    117120           td2n(ix,jy,1,n,l),tthn(ix,jy,2,n,l),ustarn(ix,jy,1,n,l), &
    118            sshfn(ix,jy,1,n,l),akm,bkm,dummyakzllev,metdata_format)
     121           sshfn(ix,jy,1,n,l),akm,bkm,dummyakzllev,id_centre)
    119122      if (ol.ne.0.) then
    120123        olin(ix,jy,1,n,l)=1./ol
     
    137140           qvlev,ulev,vlev,nuvz,akz,bkz,sshfn(ix,jy,1,n,l), &
    138141           tt2n(ix,jy,1,n,l),td2n(ix,jy,1,n,l),hmixn(ix,jy,1,n,l), &
    139            wstarn(ix,jy,1,n,l),hmixplus,metdata_format)
     142           wstarn(ix,jy,1,n,l),hmixplus,id_centre)
    140143
    141144      if(lsubgrid.eq.1) then
  • src/changelog.txt

    rf251e57 rc0884a8  
    7373   of height (array assignment where it was not intended)
    74743) Add back the SAVE attribute to INIT, just to be sure
     75
     76
     77
     78* checking type (EC/GFS) of grib files PS 2018-06-26
     79  ===================
     80replaced the CTBTO code by shorter & simper code with proper license 
     81
     82Affected files:
     83
     84calcmatrix.f90
     85calcpar.f90
     86calcpar_nests.f90
     87check_gribfile_mod.f90
     88convmix.f90
     89detectformat.f90
     90FLEXPART.f90
     91FLEXPART_MPI.f90
     92getfields.f90
     93getfields_mpi.f90
     94obukhov.f90
     95richardson.f90
     96timemanager.f90
     97timemanager_mpi.f90
  • src/convmix.f90

    r6ecb30a rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine convmix(itime,metdata_format)
     22subroutine convmix(itime,id_centre)
    2323  !                     i
    2424  !**************************************************************
     
    3939  !   Unified ECMWF and GFS builds                                             
    4040  !   Marian Harustak, 12.5.2017                                             
    41   !     - Merged convmix and convmix_gfs into one routine using if-then           
     41  !     - Merged convmix and convmix_gfs into one routine using if-then     
    4242  !       for meteo-type dependent code                                       
     43  !                                                                         
     44  !  Petra Seibert, 2018-06-26: simplified version met data format detection
     45  !                                                                         
    4346  !**************************************************************
    4447
     
    4750  use com_mod
    4851  use conv_mod
    49   use class_gribfile
     52  use check_gribfile_mod
    5053
    5154  implicit none
     
    5558  integer :: jy, kpart, ktop, ngrid,kz
    5659  integer :: igrid(maxpart), ipoint(maxpart), igridn(maxpart,maxnests)
    57   integer :: metdata_format
     60  integer :: id_centre
    5861
    5962  ! itime [s]                 current time
     
    116119
    117120    ngrid=0
    118     if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     121    if (id_centre.eq.icg_id_ecmwf) then
    119122    do j=numbnests,1,-1
    120123      if ( x.gt.xln(j)+eps .and. x.lt.xrn(j)-eps .and. &
     
    189192      td2conv=(td2(ix,jy,1,mind1)*dt2+td2(ix,jy,1,mind2)*dt1)*dtt
    190193!!$      do kz=1,nconvlev+1      !old
    191       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     194      if (id_centre.eq.icg_id_ecmwf) then
    192195        do kz=1,nuvz-1           !bugfix
    193196        tconv(kz)=(tth(ix,jy,kz+1,mind1)*dt2+ &
     
    208211
    209212  ! Calculate translocation matrix
    210       call calcmatrix(lconv,delt,cbaseflux(ix,jy),metdata_format)
     213      call calcmatrix(lconv,delt,cbaseflux(ix,jy),id_centre)
    211214      igrold = igr
    212215      ktop = 0
     
    285288  ! calculate translocation matrix
    286289  !*******************************
    287         call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest),metdata_format)
     290        call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest),id_centre)
    288291        igrold = igr
    289292        ktop = 0
  • src/getfields.f90

    r6ecb30a rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine getfields(itime,nstop,metdata_format)
     22subroutine getfields(itime,nstop,id_centre)
    2323!                       i     o
    2424!*****************************************************************************
     
    4444!   Unified ECMWF and GFS builds                                             *
    4545!   Marian Harustak, 12.5.2017                                               *
    46 !     - Added passing of metdata_format as it was needed by called routines  *
     46!     - Added passing of id_centre as it was needed by called routines       *
     47!                                                                            *
     48!  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     49!                                                                            *
    4750!*****************************************************************************
    4851!                                                                            *
     
    6265! tt(0:nxmax,0:nymax,nuvzmax,2)   temperature [K]                            *
    6366! ps(0:nxmax,0:nymax,2)           surface pressure [Pa]                      *
    64 ! metdata_format     format of metdata (ecmwf/gfs)                           *
     67! id_centre            format of metdata (ecmwf/gfs)                         *
    6568!                                                                            *
    6669! Constants:                                                                 *
     
    7275  use par_mod
    7376  use com_mod
    74   use class_gribfile
     77  use check_gribfile_mod
    7578
    7679  implicit none
    7780
    7881  integer :: indj,itime,nstop,memaux
    79   integer :: metdata_format
     82  integer :: id_centre
    8083
    8184  real :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
     
    132135    do indj=indmin,numbwf-1
    133136      if (ldirect*wftime(indj+1).gt.ldirect*itime) then
    134         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     137        if (id_centre.eq.icg_id_ecmwf) then
    135138          call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    136139        else
     
    138141        end if
    139142        call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
    140         call calcpar(memind(2),uuh,vvh,pvh,metdata_format)
    141         call calcpar_nests(memind(2),uuhn,vvhn,pvhn,metdata_format)
    142         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     143        call calcpar(memind(2),uuh,vvh,pvh,id_centre)
     144        call calcpar_nests(memind(2),uuhn,vvhn,pvhn,id_centre)
     145        if (id_centre.eq.icg_id_ecmwf) then
    143146          call verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    144147        else
     
    167170           (ldirect*wftime(indj+1).gt.ldirect*itime)) then
    168171        memind(1)=1
    169         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     172        if (id_centre.eq.icg_id_ecmwf) then
    170173          call readwind_ecmwf(indj,memind(1),uuh,vvh,wwh)
    171174        else
     
    173176        end if
    174177        call readwind_nests(indj,memind(1),uuhn,vvhn,wwhn)
    175         call calcpar(memind(1),uuh,vvh,pvh,metdata_format)
    176         call calcpar_nests(memind(1),uuhn,vvhn,pvhn,metdata_format)
    177         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     178        call calcpar(memind(1),uuh,vvh,pvh,id_centre)
     179        call calcpar_nests(memind(1),uuhn,vvhn,pvhn,id_centre)
     180        if (id_centre.eq.icg_id_ecmwf) then
    178181          call verttransform_ecmwf(memind(1),uuh,vvh,wwh,pvh)
    179182        else
     
    183186        memtime(1)=wftime(indj)
    184187        memind(2)=2
    185         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     188        if (id_centre.eq.icg_id_ecmwf) then
    186189          call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    187190        else
     
    189192        end if
    190193        call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
    191         call calcpar(memind(2),uuh,vvh,pvh,metdata_format)
    192         call calcpar_nests(memind(2),uuhn,vvhn,pvhn,metdata_format)
    193         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     194        call calcpar(memind(2),uuh,vvh,pvh,id_centre)
     195        call calcpar_nests(memind(2),uuhn,vvhn,pvhn,id_centre)
     196        if (id_centre.eq.icg_id_ecmwf) then
    194197          call verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    195198        else
  • src/getfields_mpi.f90

    r20963b1 rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine getfields(itime,nstop,memstat,metdata_format)
     22subroutine getfields(itime,nstop,memstat,id_centre)
    2323!                       i     o       o
    2424!*****************************************************************************
     
    6060!   Unified ECMWF and GFS builds                                             
    6161!   Marian Harustak, 12.5.2017                                               
    62 !     - Added passing of metdata_format as it was needed by called routines 
    63 !         
    64 !*****************************************************************************
     62!     - Added passing of id_centre as it was needed by called routines 
     63!                                                                           
     64!  Petra Seibert, 2018-06-26: simplified version met data format detection 
     65!                                                                           !*****************************************************************************
    6566!                                                                            *
    6667! Variables:                                                                 *
     
    8182! tt(0:nxmax,0:nymax,nuvzmax,numwfmem)   temperature [K]                     *
    8283! ps(0:nxmax,0:nymax,numwfmem)           surface pressure [Pa]               *
    83 ! metdata_format     format of metdata (ecmwf/gfs)                           *
     84! id_centre            format of metdata (ecmwf/gfs)                           *
    8485!                                                                            *
    8586! Constants:                                                                 *
     
    9293  use com_mod
    9394  use mpi_mod, only: lmpreader,lmp_use_reader,lmp_sync
    94   use class_gribfile
     95  use check_gribfile_mod
    9596
    9697  implicit none
    9798
    98   integer :: metdata_format
     99  integer :: id_centre
    99100  integer :: indj,itime,nstop,memaux,mindread
    100101! mindread: index of where to read 3rd field
     
    211212      if (ldirect*wftime(indj+1).gt.ldirect*itime) then
    212213        if (lmpreader.or..not. lmp_use_reader) then
    213           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     214          if (id_centre.eq.icg_id_ecmwf) then
    214215            call readwind_ecmwf(indj+1,mindread,uuh,vvh,wwh)
    215216          else
     
    217218          end if
    218219          call readwind_nests(indj+1,mindread,uuhn,vvhn,wwhn)
    219           call calcpar(mindread,uuh,vvh,pvh,metdata_format)
    220           call calcpar_nests(mindread,uuhn,vvhn,pvhn,metdata_format)
    221           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     220          call calcpar(mindread,uuh,vvh,pvh,id_centre)
     221          call calcpar_nests(mindread,uuhn,vvhn,pvhn,id_centre)
     222          if (id_centre.eq.icg_id_ecmwf) then
    222223            call verttransform_ecmwf(mindread,uuh,vvh,wwh,pvh)
    223224          else
     
    249250        memind(1)=1
    250251        if (lmpreader.or..not.lmp_use_reader) then
    251           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     252          if (id_centre.eq.icg_id_ecmwf) then
    252253            call readwind_ecmwf(indj,memind(1),uuh,vvh,wwh)
    253254          else
     
    255256          end if
    256257          call readwind_nests(indj,memind(1),uuhn,vvhn,wwhn)
    257           call calcpar(memind(1),uuh,vvh,pvh,metdata_format)
    258           call calcpar_nests(memind(1),uuhn,vvhn,pvhn,metdata_format)
    259           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     258          call calcpar(memind(1),uuh,vvh,pvh,id_centre)
     259          call calcpar_nests(memind(1),uuhn,vvhn,pvhn,id_centre)
     260          if (id_centre.eq.icg_id_ecmwf) then
    260261            call verttransform_ecmwf(memind(1),uuh,vvh,wwh,pvh)
    261262          else
     
    267268        memind(2)=2
    268269        if (lmpreader.or..not.lmp_use_reader) then
    269           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     270          if (id_centre.eq.icg_id_ecmwf) then
    270271            call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    271272          else
     
    273274          end if
    274275          call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
    275           call calcpar(memind(2),uuh,vvh,pvh,metdata_format)
    276           call calcpar_nests(memind(2),uuhn,vvhn,pvhn,metdata_format)
    277           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     276          call calcpar(memind(2),uuh,vvh,pvh,id_centre)
     277          call calcpar_nests(memind(2),uuhn,vvhn,pvhn,id_centre)
     278          if (id_centre.eq.icg_id_ecmwf) then
    278279            call verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    279280          else
  • src/makefile

    r77778f8 rc0884a8  
    2222#
    2323#    Makefile was modified to produce unified executable for both ECMWF and GFS meteo data formats
    24 #    gributils were included to detect format of meteo data
    2524#
    2625#    Cpp directives USE_MPIINPLACE were added to three source files. The effect of these directives
     
    106105
    107106#FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -cpp -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(NCOPT) $(FUSER)  #-Warray-bounds -fcheck=all # -march=native
    108 FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -cpp -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(NCOPT) $(FUSER)  # -fcheck=all -fbacktrace -march=native
     107#FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -cpp -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(NCOPT) $(FUSER)  # -fcheck=all -fbacktrace -march=native
     108FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -cpp -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(NCOPT) $(FUSER)  -fcheck=all -fbacktrace -march=native
    109109
    110110# Explanation of unusual gfortran options
     
    125125point_mod.o             outg_mod.o \
    126126mean_mod.o              random_mod.o \
    127 class_gribfile_mod.o
     127check_gribfile_mod.o   
     128
    128129
    129130MPI_MODOBJS = \
     
    197198interpol_wind_nests.o   interpol_misslev_nests.o \
    198199interpol_vdep_nests.o   interpol_rain_nests.o \
    199 readageclasses.o        detectformat.o  \
     200readageclasses.o        \
    200201calcfluxes.o            fluxoutput.o \
    201202qvsat.o                 skplin.o \
     
    272273        random_mod.o
    273274calcfluxes.o: com_mod.o flux_mod.o outg_mod.o par_mod.o
    274 calcmatrix.o: com_mod.o conv_mod.o par_mod.o class_gribfile_mod.o
    275 calcpar.o: com_mod.o par_mod.o class_gribfile_mod.o
     275calcmatrix.o: check_gribfile_mod.o conv_mod.o com_mod.o par_mod.o
     276calcpar.o: com_mod.o par_mod.o check_gribfile_mod.o
    276277calcpar_nests.o: com_mod.o par_mod.o
    277278calcpv.o: com_mod.o par_mod.o
     
    299300conv_mod.o: par_mod.o
    300301convect43c.o: conv_mod.o par_mod.o
    301 convmix.o: com_mod.o conv_mod.o flux_mod.o par_mod.o class_gribfile_mod.o
     302convmix.o: com_mod.o conv_mod.o flux_mod.o par_mod.o check_gribfile_mod.o
    302303coordtrafo.o: com_mod.o par_mod.o point_mod.o
    303 detectformat.o: com_mod.o par_mod.o class_gribfile_mod.o
    304304distance.o: par_mod.o
    305305distance2.o: par_mod.o
     
    307307drydepokernel_nest.o: com_mod.o par_mod.o unc_mod.o
    308308erf.o: par_mod.o
    309 FLEXPART.o: com_mod.o conv_mod.o par_mod.o point_mod.o random_mod.o netcdf_output_mod.o class_gribfile_mod.o
     309FLEXPART.o: com_mod.o conv_mod.o par_mod.o point_mod.o random_mod.o netcdf_output_mod.o check_gribfile_mod.o
     310FLEXPART.o: check_gribfile_mod.o random_mod.o conv_mod.o com_mod.o par_mod.o point_mod.o
    310311FLEXPART_MPI.o: com_mod.o conv_mod.o mpi_mod.o par_mod.o point_mod.o \
    311         random_mod.o netcdf_output_mod.o class_gribfile_mod.o
     312        random_mod.o netcdf_output_mod.o check_gribfile_mod.o
    312313fluxoutput.o: com_mod.o flux_mod.o outg_mod.o par_mod.o
    313314get_settling.o: com_mod.o par_mod.o
    314 getfields.o: com_mod.o par_mod.o class_gribfile_mod.o
    315 getfields_mpi.o: com_mod.o par_mod.o mpi_mod.o class_gribfile_mod.o
     315getfields.o: com_mod.o par_mod.o check_gribfile_mod.o
     316getfields_mpi.o: com_mod.o par_mod.o mpi_mod.o check_gribfile_mod.o
    316317gethourlyOH.o: com_mod.o oh_mod.o par_mod.o
    317318getrb.o: par_mod.o
     
    354355mpi_mod.o: com_mod.o par_mod.o unc_mod.o
    355356netcdf_output_mod.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    356 obukhov.o: par_mod.o class_gribfile_mod.o
     357obukhov.o: par_mod.o check_gribfile_mod.o
    357358ohreaction.o: com_mod.o oh_mod.o par_mod.o
    358359openouttraj.o: com_mod.o par_mod.o point_mod.o
     
    401402releaseparticles_mpi.o: com_mod.o mpi_mod.o par_mod.o point_mod.o \
    402403        random_mod.o xmass_mod.o
    403 richardson.o: par_mod.o class_gribfile_mod.o
     404richardson.o: par_mod.o check_gribfile_mod.o
    404405scalev.o: par_mod.o
    405406shift_field.o: par_mod.o
  • src/obukhov.f90

    r6ecb30a rc0884a8  
    2020!**********************************************************************
    2121
    22 real function obukhov(ps,tsurf,tdsurf,tlev,ustar,hf,akm,bkm,plev,metdata_format)
     22real function obukhov(ps,tsurf,tdsurf,tlev,ustar,hf,akm,bkm,plev,id_centre)
    2323
    2424  !********************************************************************
     
    4141  !       if-then for meteo-type dependent code                       *
    4242  !                                                                   *
     43  !                                                                   *
     44  !  Petra Seibert, 2018-06-26:                                       *
     45  !    simplified version met data format detection                   *
     46  !                                                                   *
    4347  !********************************************************************
    4448  !                                                                   *
     
    5458  !     bkm     ECMWF vertical discretization parameter               *
    5559  !     plev                                                          *
    56   !     metdata_format format of metdata (ecmwf/gfs)                  *
     60  !     id_centre format of metdata (ecmwf/gfs)                  *
    5761  !                                                                   *
    5862  !********************************************************************
    5963
    6064  use par_mod
    61   use class_gribfile
     65  use check_gribfile_mod
    6266
    6367  implicit none
    6468
    65   integer :: metdata_format
     69  integer :: id_centre
    6670  real :: akm(nwzmax),bkm(nwzmax)
    6771  real :: ps,tsurf,tdsurf,tlev,ustar,hf,e,ew,tv,rhoa,plev
     
    7276  tv=tsurf*(1.+0.378*e/ps)               ! virtual temperature
    7377  rhoa=ps/(r_air*tv)                      ! air density
    74   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     78  if (id_centre.eq.icg_id_ecmwf) then
    7579  ak1=(akm(1)+akm(2))/2.
    7680  bk1=(bkm(1)+bkm(2))/2.
  • src/par_mod.f90

    r1f55de1 rc0884a8  
    147147 
    148148  ! ECMWF
    149 ! integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=359 ! 1.0 degree 92 level
    150   integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359 ! 1.0 degree 138 level
     149 integer,parameter :: nxmax=721,nymax=362,nuvzmax=36,nwzmax=36,nzmax=36,nxshift=0 ! 1.0 degree 92 level
     150!  integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359 ! 1.0 degree 138 level
    151151! integer,parameter :: nxmax=721,nymax=361,nuvzmax=138,nwzmax=138,nzmax=138,nxshift=359  ! 0.5 degree 138 level
    152152!  integer,parameter :: nxmax=181,nymax=91,nuvzmax=92,nwzmax=92,nzmax=92,nxshift=0  ! CERA 2.0 degree 92 level
  • src/richardson.f90

    r6ecb30a rc0884a8  
    2121
    2222subroutine richardson(psurf,ust,ttlev,qvlev,ulev,vlev,nuvz, &
    23        akz,bkz,hf,tt2,td2,h,wst,hmixplus,metdata_format)
     23       akz,bkz,hf,tt2,td2,h,wst,hmixplus,id_centre)
    2424  !                        i    i    i     i    i    i    i
    2525  ! i   i  i   i   i  o  o     o
     
    4141  !     Meteor. 81, 245-269.                                                  *
    4242  !                                                                           *
     43  !                                                                           *
     44  !  Petra Seibert, 2018-06-26: simplified version met data format detection  *
     45  !                                                                           *
    4346  !****************************************************************************
    4447  !                                                                           *
     
    5558  !       - Merged richardson and richardson_gfs into one routine using       *
    5659  !         if-then for meteo-type dependent code                             *
     60  !                                                                           *
     61  !                                                                           *
     62  !  Petra Seibert, 2018-06-26: simplified version met data format detection  *
    5763  !                                                                           *
    5864  !****************************************************************************
     
    6470  ! tv                         virtual temperature                            *
    6571  ! wst                        convective velocity scale                      *
    66   ! metdata_format             format of metdata (ecmwf/gfs)                  *
     72  ! id_centre                  format of metdata (ecmwf/gfs)                  *
    6773  !                                                                           *
    6874  ! Constants:                                                                *
     
    7278
    7379  use par_mod
    74   use class_gribfile
     80  use check_gribfile_mod
    7581
    7682  implicit none
    7783
    78   integer :: metdata_format
     84  integer :: id_centre
    7985  integer :: i,k,nuvz,iter,llev,loop_start
    8086  real :: tv,tvold,zref,z,zold,pint,pold,theta,thetaref,ri
     
    8995  iter=0
    9096
    91   if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
     97  if (id_centre.eq.icg_id_ncep) then
    9298    ! NCEP version: find first model level above ground
    9399    !**************************************************
     
    123129  ! Integrate z up to one level above zt
    124130  !*************************************
    125   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
     131  if (id_centre.eq.icg_id_ecmwf) then
    126132    loop_start=2
    127133  else
  • src/timemanager.f90

    ra9cf4b1 rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine timemanager(metdata_format)
     22subroutine timemanager(id_centre)
    2323
    2424  !*****************************************************************************
     
    5252  !  Unified ECMWF and GFS builds                                              *
    5353  !   Marian Harustak, 12.5.2017                                               *
    54   !   - Added passing of metdata_format as it was needed by called routines    *
     54  !   - Added passing of id_centre as it was needed by called routines         *
     55  !                                                                            *
     56  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     57  !                                                                            *
    5558  !*****************************************************************************
    5659  !                                                                            *
     
    8689  ! xtra1(maxpart), ytra1(maxpart), ztra1(maxpart) =                           *
    8790  !                    spatial positions of trajectories                       *
    88   ! metdata_format     format of metdata (ecmwf/gfs)                           *
     91  ! id_centre          format of metdata (ecmwf/gfs)                           *
    8992  !                                                                            *
    9093  ! Constants:                                                                 *
     
    108111  implicit none
    109112
    110   integer :: metdata_format
     113  integer :: id_centre
    111114  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1
    112115! integer :: ksp
     
    201204           write (*,*) 'timemanager> call convmix -- backward'
    202205        endif         
    203       call convmix(itime,metdata_format)
     206      call convmix(itime,id_centre)
    204207        if (verbosity.gt.1) then
    205208          !CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     
    214217           write (*,*) 'timemanager> call getfields'
    215218    endif
    216     call getfields(itime,nstop1,metdata_format)
     219    call getfields(itime,nstop1,id_centre)
    217220        if (verbosity.gt.1) then
    218221          CALL SYSTEM_CLOCK(count_clock)
     
    273276       write (*,*) 'timemanager> call convmix -- forward'
    274277     endif   
    275      call convmix(itime,metdata_format)
     278     call convmix(itime,id_centre)
    276279   endif
    277280
  • src/timemanager_mpi.f90

    r20963b1 rc0884a8  
    2020!**********************************************************************
    2121
    22 subroutine timemanager(metdata_format)
     22subroutine timemanager(id_centre)
    2323
    2424!*****************************************************************************
     
    5252!  Unified ECMWF and GFS builds                                              *
    5353!   Marian Harustak, 12.5.2017                                               *
    54 !   - Added passing of metdata_format as it was needed by called routines    *
     54!   - Added passing of id_centre as it was needed by called routines         *
     55!                                                                            *
     56!  Petra Seibert, 2018-06-26: simplified version met data format detection   *
     57!                                                                            *
    5558!*****************************************************************************
    5659!                                                                            *
     
    8689! xtra1(maxpart), ytra1(maxpart), ztra1(maxpart) =                           *
    8790!                    spatial positions of trajectories                       *
    88 ! metdata_format     format of metdata (ecmwf/gfs)                           *
     91! id_centre          format of metdata (ecmwf/gfs)                           *
    8992!                                                                            *
    9093! Constants:                                                                 *
     
    109112  implicit none
    110113
    111   integer :: metdata_format
     114  integer :: id_centre
    112115  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
    113116  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1,memstat=0
     
    214217      endif
    215218! readwind process skips this step
    216       if (.not.(lmpreader.and.lmp_use_reader)) call convmix(itime,metdata_format)
     219      if (.not.(lmpreader.and.lmp_use_reader)) call convmix(itime,id_centre)
    217220    endif
    218221
     
    227230    if (mp_measure_time) call mpif_mtime('getfields',0)
    228231
    229     call getfields(itime,nstop1,memstat,metdata_format)
     232    call getfields(itime,nstop1,memstat,id_centre)
    230233
    231234    if (mp_measure_time) call mpif_mtime('getfields',1)
     
    355358        write (*,*) 'timemanager> call convmix -- forward'
    356359      endif
    357       call convmix(itime,metdata_format)
     360      call convmix(itime,id_centre)
    358361    endif
    359362
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG