Changeset c0884a8 in flexpart.git for src/calcpar.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/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
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG