Changes in / [bb579a9:aa8c34a] in flexpart.git


Ignore:
Files:
8 added
9 deleted
26 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART.f90

    rd8eed02 rc8fc724  
    3333  !                                                                            *
    3434  !*****************************************************************************
    35   ! Changes:                                                                   *
    36   !   Unified ECMWF and GFS builds                                             *
    37   !   Marian Harustak, 12.5.2017                                               *
    38   !     - Added detection of metdata format using gributils routines           *
    39   !     - Distinguished calls to ecmwf/gfs gridcheck versions based on         *
    40   !       detected metdata format                                              *
    41   !     - Passed metdata format down to timemanager                            *
    42   !*****************************************************************************
    4335  !                                                                            *
    4436  ! Variables:                                                                 *
     
    5446  use netcdf_output_mod, only: writeheader_netcdf
    5547  use random_mod, only: gasdev1
    56   use class_gribfile
    5748
    5849  implicit none
     
    6152  integer :: idummy = -320
    6253  character(len=256) :: inline_options  !pathfile, flexversion, arg2
    63   integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
    64   integer :: detectformat
    65 
    6654
    6755
     
    8270  ! FLEXPART version string
    8371  flexversion_major = '10' ! Major version number, also used for species file names
    84   flexversion='Version '//trim(flexversion_major)//'.2beta (2017-08-01)'
     72  flexversion='Version '//trim(flexversion_major)//'.1beta (2016-11-02)'
    8573  verbosity=0
    8674
     
    184172  call readavailable
    185173
    186   ! Detect metdata format
    187   !**********************
    188 
    189   metdata_format = detectformat()
    190 
    191   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    192     print *,'ECMWF metdata detected'
    193   elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    194     print *,'NCEP metdata detected'
    195   else
    196     print *,'Unknown metdata format'
    197     return
    198   endif
    199 
    200 
    201 
    202174  ! If nested wind fields are used, allocate arrays
    203175  !************************************************
     
    216188  endif
    217189
    218   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    219     call gridcheck_ecmwf
    220   else
    221     call gridcheck_gfs
    222   end if
     190  call gridcheck
    223191
    224192  if (verbosity.gt.1) then   
     
    443411  endif
    444412
    445   call timemanager(metdata_format)
     413  call timemanager
    446414
    447415! NIK 16.02.2005
  • src/FLEXPART_MPI.f90

    rd8eed02 r5184a7c  
    3333  !                                                                            *
    3434  !*****************************************************************************
    35   ! Changes:                                                                   *
    36   !   Unified ECMWF and GFS builds                                             *
    37   !   Marian Harustak, 12.5.2017                                               *
    38   !     - Added detection of metdata format using gributils routines           *
    39   !     - Distinguished calls to ecmwf/gfs gridcheck versions based on         *
    40   !       detected metdata format                                              *
    41   !     - Passed metdata format down to timemanager                            *
    42   !*****************************************************************************
    4335  !                                                                            *
    4436  ! Variables:                                                                 *
     
    5547  use netcdf_output_mod, only: writeheader_netcdf
    5648  use random_mod, only: gasdev1
    57   use class_gribfile
    5849
    5950  implicit none
     
    6253  integer :: idummy = -320
    6354  character(len=256) :: inline_options  !pathfile, flexversion, arg2
    64   integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
    65   integer :: detectformat
    66 
    6755
    6856
     
    9280  ! FLEXPART version string
    9381  flexversion_major = '10' ! Major version number, also used for species file names
    94   flexversion='Ver. '//trim(flexversion_major)//'.2beta MPI (2017-08-01)'
     82  flexversion='Ver. '//trim(flexversion_major)//'.1beta MPI (2016-11-02)'
    9583  verbosity=0
    9684
     
    209197  call readavailable
    210198
    211   ! Detect metdata format
    212   !**********************
    213 
    214   metdata_format = detectformat()
    215 
    216   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    217     print *,'ECMWF metdata detected'
    218   elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    219     print *,'NCEP metdata detected'
    220   else
    221     print *,'Unknown metdata format'
    222     return
    223   endif
    224 
    225 
    226 
    227199  ! If nested wind fields are used, allocate arrays
    228200  !************************************************
     
    241213  endif
    242214
    243   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    244     call gridcheck_ecmwf
    245   else
    246     call gridcheck_gfs
    247   end if
    248 
     215  call gridcheck
    249216
    250217  if (verbosity.gt.1 .and. lroot) then   
     
    489456
    490457
    491   call timemanager(metdata_format)
     458  call timemanager
    492459
    493460
  • src/calcmatrix.f90

    rd8eed02 re200b7a  
    2020!**********************************************************************
    2121
    22 subroutine calcmatrix(lconv,delt,cbmf,metdata_format)
     22subroutine calcmatrix(lconv,delt,cbmf)
    2323  !                        o    i    o
    2424  !*****************************************************************************
     
    3030  !  Petra Seibert, Bernd C. Krueger, 2000-2001                                *
    3131  !                                                                            *
    32   !*****************************************************************************
    33   ! Changes:                                                                   *
    3432  !  changed by C. Forster, November 2003 - February 2004                      *
    3533  !  array fmassfrac(nconvlevmax,nconvlevmax) represents                       *
    3634  !  the convective redistribution matrix for the particles                    *
    3735  !                                                                            *
    38   !   Unified ECMWF and GFS builds                                             *
    39   !   Marian Harustak, 12.5.2017                                               *
    40   !     - Merged calcmatrix and calcmatrix_gfs into one routine using if-then  *
    41   !       for meteo-type dependent code                                        *
    42   !*****************************************************************************
    43   !                                                                            *
    4436  !  lconv        indicates whether there is convection in this cell, or not   *
    4537  !  delt         time step for convection [s]                                 *
    4638  !  cbmf         cloud base mass flux                                         *
    47   !  metdata_format format of metdata (ecmwf/gfs)                              *
    4839  !                                                                            *
    4940  !*****************************************************************************
     
    5243  use com_mod
    5344  use conv_mod
    54   use class_gribfile
    5545
    5646  implicit none
    5747
    5848  real :: rlevmass,summe
    59   integer :: metdata_format
    6049
    6150  integer :: iflag, k, kk, kuvz
     
    8877  do kuvz = 2,nuvz
    8978    k = kuvz-1
    90     if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    9179    pconv(k) = (akz(kuvz) + bkz(kuvz)*psconv)
    9280    phconv(kuvz) = (akm(kuvz) + bkm(kuvz)*psconv)
    93     else
    94       phconv(kuvz) =  0.5*(pconv(kuvz)+pconv(k))
    95     endif
    9681    dpr(k) = phconv(k) - phconv(kuvz)
    9782    qsconv(k) = f_qvsat( pconv(k), tconv(k) )
     
    10085    do kk=1,nconvlev
    10186      fmassfrac(k,kk)=0.
    102     end do
    103   end do
     87    enddo
     88  enddo
    10489
    10590
  • src/calcpar.f90

    r6ecb30a re200b7a  
    2020!**********************************************************************
    2121
    22 subroutine calcpar(n,uuh,vvh,pvh,metdata_format)
     22subroutine calcpar(n,uuh,vvh,pvh)
    2323  !                   i  i   i   o
    2424  !*****************************************************************************
     
    3737  !     new variables in call to richardson                                    *
    3838  !                                                                            *
    39   !   CHANGE 17/11/2005 Caroline Forster NCEP GFS version                      *
    40   !                                                                            *
    41   !   Changes, Bernd C. Krueger, Feb. 2001:                                    *
    42   !    Variables tth and qvh (on eta coordinates) in common block              *
    43   !                                                                            *
    44   !   Unified ECMWF and GFS builds                                             *
    45   !   Marian Harustak, 12.5.2017                                               *
    46   !     - Merged calcpar and calcpar_gfs into one routine using if-then        *
    47   !       for meteo-type dependent code                                        *
    48   !*****************************************************************************
    49 
     39  !*****************************************************************************
     40  !  Changes, Bernd C. Krueger, Feb. 2001:
     41  !   Variables tth and qvh (on eta coordinates) in common block
    5042  !*****************************************************************************
    5143  !                                                                            *
    5244  ! Variables:                                                                 *
    5345  ! n                  temporal index for meteorological fields (1 to 3)       *
    54   ! uuh                                                                        *
    55   ! vvh                                                                        *
    56   ! pvh                                                                        *
    57   ! metdata_format     format of metdata (ecmwf/gfs)                           *
    5846  !                                                                            *
    5947  ! Constants:                                                                 *
     
    6856  use par_mod
    6957  use com_mod
    70   use class_gribfile
    7158
    7259  implicit none
    7360
    74   integer :: metdata_format
    75   integer :: n,ix,jy,i,kz,lz,kzmin,llev,loop_start
     61  integer :: n,ix,jy,i,kz,lz,kzmin
    7662  real :: ttlev(nuvzmax),qvlev(nuvzmax),obukhov,scalev,ol,hmixplus
    7763  real :: ulev(nuvzmax),vlev(nuvzmax),ew,rh,vd(maxspec),subsceff,ylat
    78   real :: altmin,tvold,pold,zold,pint,tv,zlev(nuvzmax),hmixdummy
     64  real :: altmin,tvold,pold,zold,pint,tv,zlev(nuvzmax)
    7965  real :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
    8066  real :: vvh(0:nxmax-1,0:nymax-1,nuvzmax)
     
    125111  !***********************************************
    126112
    127       if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    128         ! NCEP version: find first level above ground
    129         llev = 0
    130         do i=1,nuvz
    131           if (ps(ix,jy,1,n).lt.akz(i)) llev=i
    132         end do
    133         llev = llev+1
    134         if (llev.gt.nuvz) llev = nuvz-1
    135         ! NCEP version
    136 
    137         ! calculate inverse Obukhov length scale with tth(llev)
    138113      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       else
    141         llev=0
    142         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,akz(llev),metdata_format)
    144       end if
    145 
     114           tth(ix,jy,2,n),ustar(ix,jy,1,n),sshf(ix,jy,1,n),akm,bkm)
    146115      if (ol.ne.0.) then
    147116        oli(ix,jy,1,n)=1./ol
     
    161130      end do
    162131
    163       if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    164         ! NCEP version hmix has been read in in readwind.f, is therefore not calculated here
    165132      call richardson(ps(ix,jy,1,n),ustar(ix,jy,1,n),ttlev,qvlev, &
    166133           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)
    168       else
    169         call richardson(ps(ix,jy,1,n),ustar(ix,jy,1,n),ttlev,qvlev, &
    170              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)
    172       end if
     134           td2(ix,jy,1,n),hmix(ix,jy,1,n),wstar(ix,jy,1,n),hmixplus)
    173135
    174136      if(lsubgrid.eq.1) then
     
    211173  !******************************************************
    212174
    213   ! 1) Calculate altitudes of model levels
    214   !***************************************
     175  ! 1) Calculate altitudes of ECMWF model levels
     176  !*********************************************
    215177
    216178      tvold=tt2(ix,jy,1,n)*(1.+0.378*ew(td2(ix,jy,1,n))/ &
     
    218180      pold=ps(ix,jy,1,n)
    219181      zold=0.
    220       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    221         loop_start=2
    222       else
    223         loop_start=llev
    224       end if
    225       do kz=loop_start,nuvz
     182      do kz=2,nuvz
    226183        pint=akz(kz)+bkz(kz)*ps(ix,jy,1,n)  ! pressure on model layers
    227184        tv=tth(ix,jy,kz,n)*(1.+0.608*qvh(ix,jy,kz,n))
     
    242199  !************************************************************************
    243200
    244       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    245         loop_start=1
    246       else
    247         loop_start=llev
    248       end if
    249 
    250       do kz=loop_start,nuvz
     201      do kz=1,nuvz
    251202        if (zlev(kz).ge.altmin) then
    252203          kzmin=kz
  • src/calcpar_nests.f90

    r6ecb30a rdb712a8  
    2020!**********************************************************************
    2121
    22 subroutine calcpar_nests(n,uuhn,vvhn,pvhn,metdata_format)
     22subroutine calcpar_nests(n,uuhn,vvhn,pvhn)
    2323  !                         i  i    i    o
    2424  !*****************************************************************************
     
    3939  !                                                                            *
    4040  !*****************************************************************************
    41   !  Changes, Bernd C. Krueger, Feb. 2001:                                     *
    42   !   Variables tth and qvh (on eta coordinates) in common block               *
    43   !                                                                            *
    44   !   Unified ECMWF and GFS builds                                             *
    45   !   Marian Harustak, 12.5.2017                                               *
    46   !     - Added passing of metdata_format as it was needed by called routines  *
     41  !  Changes, Bernd C. Krueger, Feb. 2001:
     42  !   Variables tth and qvh (on eta coordinates) in common block
    4743  !*****************************************************************************
    4844  !                                                                            *
    4945  ! Variables:                                                                 *
    5046  ! n                  temporal index for meteorological fields (1 to 3)       *
    51   ! metdata_format     format of metdata (ecmwf/gfs)                           *
    5247  !                                                                            *
    5348  ! Constants:                                                                 *
     
    6560  implicit none
    6661
    67   integer :: metdata_format
    6862  integer :: n,ix,jy,i,l,kz,lz,kzmin
    69   real :: ttlev(nuvzmax),qvlev(nuvzmax),obukhov,scalev,ol,hmixplus,dummyakzllev
     63  real :: ttlev(nuvzmax),qvlev(nuvzmax),obukhov,scalev,ol,hmixplus
    7064  real :: ulev(nuvzmax),vlev(nuvzmax),ew,rh,vd(maxspec),subsceff,ylat
    7165  real :: altmin,tvold,pold,zold,pint,tv,zlev(nuvzmax)
     
    116110      ol=obukhov(psn(ix,jy,1,n,l),tt2n(ix,jy,1,n,l), &
    117111           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)
     112           sshfn(ix,jy,1,n,l),akm,bkm)
    119113      if (ol.ne.0.) then
    120114        olin(ix,jy,1,n,l)=1./ol
     
    137131           qvlev,ulev,vlev,nuvz,akz,bkz,sshfn(ix,jy,1,n,l), &
    138132           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)
     133           wstarn(ix,jy,1,n,l),hmixplus)
    140134
    141135      if(lsubgrid.eq.1) then
  • src/convmix.f90

    r6ecb30a r8a65cb0  
    2020!**********************************************************************
    2121
    22 subroutine convmix(itime,metdata_format)
     22subroutine convmix(itime)
    2323  !                     i
    2424  !**************************************************************
     
    3131  !CHANGES by A. Stohl:
    3232  !  various run-time optimizations - February 2005
    33   ! CHANGES by C. Forster, November 2005, NCEP GFS version
    34   !      in the ECMWF version convection is calculated on the
    35   !      original eta-levels
    36   !      in the GFS version convection is calculated on the
    37   !      FLEXPART levels
    38   !
    39   !   Unified ECMWF and GFS builds                                             
    40   !   Marian Harustak, 12.5.2017                                             
    41   !     - Merged convmix and convmix_gfs into one routine using if-then           
    42   !       for meteo-type dependent code                                       
    4333  !**************************************************************
    4434
     
    4737  use com_mod
    4838  use conv_mod
    49   use class_gribfile
    5039
    5140  implicit none
     
    5544  integer :: jy, kpart, ktop, ngrid,kz
    5645  integer :: igrid(maxpart), ipoint(maxpart), igridn(maxpart,maxnests)
    57   integer :: metdata_format
    5846
    5947  ! itime [s]                 current time
     
    116104
    117105    ngrid=0
    118     if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    119106    do j=numbnests,1,-1
    120107      if ( x.gt.xln(j)+eps .and. x.lt.xrn(j)-eps .and. &
     
    124111      endif
    125112    end do
    126     else
    127       do j=numbnests,1,-1
    128         if ( x.gt.xln(j) .and. x.lt.xrn(j) .and. &
    129              y.gt.yln(j) .and. y.lt.yrn(j) ) then
    130           ngrid=j
    131           goto 23
    132         endif
    133       end do
    134     endif
    135113 23   continue
    136114
     
    189167      td2conv=(td2(ix,jy,1,mind1)*dt2+td2(ix,jy,1,mind2)*dt1)*dtt
    190168!!$      do kz=1,nconvlev+1      !old
    191       if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    192169        do kz=1,nuvz-1           !bugfix
    193170        tconv(kz)=(tth(ix,jy,kz+1,mind1)*dt2+ &
     
    196173             qvh(ix,jy,kz+1,mind2)*dt1)*dtt
    197174      end do
    198       else
    199         do kz=1,nuvz-1           !bugfix
    200           pconv(kz)=(pplev(ix,jy,kz,mind1)*dt2+ &
    201               pplev(ix,jy,kz,mind2)*dt1)*dtt
    202           tconv(kz)=(tt(ix,jy,kz,mind1)*dt2+ &
    203               tt(ix,jy,kz,mind2)*dt1)*dtt
    204           qconv(kz)=(qv(ix,jy,kz,mind1)*dt2+ &
    205               qv(ix,jy,kz,mind2)*dt1)*dtt
    206         end do
    207       end if
    208175
    209176  ! Calculate translocation matrix
    210       call calcmatrix(lconv,delt,cbaseflux(ix,jy),metdata_format)
     177      call calcmatrix(lconv,delt,cbaseflux(ix,jy))
    211178      igrold = igr
    212179      ktop = 0
     
    285252  ! calculate translocation matrix
    286253  !*******************************
    287         call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest),metdata_format)
     254        call calcmatrix(lconv,delt,cbasefluxn(ix,jy,inest))
    288255        igrold = igr
    289256        ktop = 0
  • src/getfields.f90

    r6ecb30a rd1a8707  
    2020!**********************************************************************
    2121
    22 subroutine getfields(itime,nstop,metdata_format)
     22subroutine getfields(itime,nstop)
    2323!                       i     o
    2424!*****************************************************************************
     
    3838!                                                                            *
    3939!*****************************************************************************
    40 !  Changes, Bernd C. Krueger, Feb. 2001:                                     *
    41 !   Variables tth,qvh,tthn,qvhn (on eta coordinates) in common block.        *
    42 !   Function of nstop extended.                                              *
    43 !                                                                            *
    44 !   Unified ECMWF and GFS builds                                             *
    45 !   Marian Harustak, 12.5.2017                                               *
    46 !     - Added passing of metdata_format as it was needed by called routines  *
     40!  Changes, Bernd C. Krueger, Feb. 2001:
     41!   Variables tth,qvh,tthn,qvhn (on eta coordinates) in common block.
     42!   Function of nstop extended.
    4743!*****************************************************************************
    4844!                                                                            *
     
    6258! tt(0:nxmax,0:nymax,nuvzmax,2)   temperature [K]                            *
    6359! ps(0:nxmax,0:nymax,2)           surface pressure [Pa]                      *
    64 ! metdata_format     format of metdata (ecmwf/gfs)                           *
    6560!                                                                            *
    6661! Constants:                                                                 *
     
    7267  use par_mod
    7368  use com_mod
    74   use class_gribfile
    7569
    7670  implicit none
    7771
    7872  integer :: indj,itime,nstop,memaux
    79   integer :: metdata_format
    8073
    8174  real :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
     
    132125    do indj=indmin,numbwf-1
    133126      if (ldirect*wftime(indj+1).gt.ldirect*itime) then
    134         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    135           call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    136         else
    137           call readwind_gfs(indj+1,memind(2),uuh,vvh,wwh)
    138         end if
     127        call readwind(indj+1,memind(2),uuh,vvh,wwh)
    139128        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 verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    144         else
    145           call verttransform_gfs(memind(2),uuh,vvh,wwh,pvh)
    146         end if
     129        call calcpar(memind(2),uuh,vvh,pvh)
     130        call calcpar_nests(memind(2),uuhn,vvhn,pvhn)
     131        call verttransform(memind(2),uuh,vvh,wwh,pvh)
    147132        call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
    148133        memtime(2)=wftime(indj+1)
     
    167152           (ldirect*wftime(indj+1).gt.ldirect*itime)) then
    168153        memind(1)=1
    169         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    170           call readwind_ecmwf(indj,memind(1),uuh,vvh,wwh)
    171         else
    172           call readwind_gfs(indj,memind(1),uuh,vvh,wwh)
    173         end if
     154        call readwind(indj,memind(1),uuh,vvh,wwh)
    174155        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 verttransform_ecmwf(memind(1),uuh,vvh,wwh,pvh)
    179         else
    180           call verttransform_gfs(memind(1),uuh,vvh,wwh,pvh)
    181         end if
     156        call calcpar(memind(1),uuh,vvh,pvh)
     157        call calcpar_nests(memind(1),uuhn,vvhn,pvhn)
     158        call verttransform(memind(1),uuh,vvh,wwh,pvh)
    182159        call verttransform_nests(memind(1),uuhn,vvhn,wwhn,pvhn)
    183160        memtime(1)=wftime(indj)
    184161        memind(2)=2
    185         if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    186           call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    187         else
    188           call readwind_gfs(indj+1,memind(2),uuh,vvh,wwh)
    189         end if
     162        call readwind(indj+1,memind(2),uuh,vvh,wwh)
    190163        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 verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    195         else
    196           call verttransform_gfs(memind(2),uuh,vvh,wwh,pvh)
    197         end if
     164        call calcpar(memind(2),uuh,vvh,pvh)
     165        call calcpar_nests(memind(2),uuhn,vvhn,pvhn)
     166        call verttransform(memind(2),uuh,vvh,wwh,pvh)
    198167        call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
    199168        memtime(2)=wftime(indj+1)
  • src/getfields_mpi.f90

    r6ecb30a r78e62dc  
    2020!**********************************************************************
    2121
    22 subroutine getfields(itime,nstop,memstat,metdata_format)
     22subroutine getfields(itime,nstop,memstat)
    2323!                       i     o       o
    2424!*****************************************************************************
     
    5858!    memstat=0:      no new fields to be read
    5959!         
    60 !   Unified ECMWF and GFS builds                                             
    61 !   Marian Harustak, 12.5.2017                                               
    62 !     - Added passing of metdata_format as it was needed by called routines 
    63 !         
    6460!*****************************************************************************
    6561!                                                                            *
     
    8177! tt(0:nxmax,0:nymax,nuvzmax,numwfmem)   temperature [K]                     *
    8278! ps(0:nxmax,0:nymax,numwfmem)           surface pressure [Pa]               *
    83 ! metdata_format     format of metdata (ecmwf/gfs)                           *
    8479!                                                                            *
    8580! Constants:                                                                 *
     
    9287  use com_mod
    9388  use mpi_mod, only: lmpreader,lmp_use_reader,lmp_sync
    94   use class_gribfile
    9589
    9690  implicit none
    9791
    98   integer :: metdata_format
    9992  integer :: indj,itime,nstop,memaux,mindread
    10093! mindread: index of where to read 3rd field
     
    211204      if (ldirect*wftime(indj+1).gt.ldirect*itime) then
    212205        if (lmpreader.or..not. lmp_use_reader) then
    213           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    214             call readwind_ecmwf(indj+1,mindread,uuh,vvh,wwh)
    215           else
    216             call readwind_gfs(indj+1,mindread,uuh,vvh,wwh)
    217           end if
     206          call readwind(indj+1,mindread,uuh,vvh,wwh)
    218207          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
    222             call verttransform_ecmwf(mindread,uuh,vvh,wwh,pvh)
    223           else
    224             call verttransform_gfs(mindread,uuh,vvh,wwh,pvh)
    225           end if
     208          call calcpar(mindread,uuh,vvh,pvh)
     209          call calcpar_nests(mindread,uuhn,vvhn,pvhn)
     210          call verttransform(mindread,uuh,vvh,wwh,pvh)
    226211          call verttransform_nests(mindread,uuhn,vvhn,wwhn,pvhn)
    227212        end if
     
    245230        memind(1)=1
    246231        if (lmpreader.or..not.lmp_use_reader) then
    247           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    248             call readwind_ecmwf(indj,memind(1),uuh,vvh,wwh)
    249           else
    250             call readwind_gfs(indj,memind(1),uuh,vvh,wwh)
    251           end if
     232          call readwind(indj,memind(1),uuh,vvh,wwh)
    252233          call readwind_nests(indj,memind(1),uuhn,vvhn,wwhn)
    253           call calcpar(memind(1),uuh,vvh,pvh,metdata_format)
    254           call calcpar_nests(memind(1),uuhn,vvhn,pvhn,metdata_format)
    255           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    256             call verttransform_ecmwf(memind(1),uuh,vvh,wwh,pvh)
    257           else
    258             call verttransform_gfs(memind(1),uuh,vvh,wwh,pvh)
    259           end if
     234          call calcpar(memind(1),uuh,vvh,pvh)
     235          call calcpar_nests(memind(1),uuhn,vvhn,pvhn)
     236          call verttransform(memind(1),uuh,vvh,wwh,pvh)
    260237          call verttransform_nests(memind(1),uuhn,vvhn,wwhn,pvhn)
    261238        end if
     
    263240        memind(2)=2
    264241        if (lmpreader.or..not.lmp_use_reader) then
    265           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    266             call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
    267           else
    268             call readwind_gfs(indj+1,memind(2),uuh,vvh,wwh)
    269           end if
     242          call readwind(indj+1,memind(2),uuh,vvh,wwh)
    270243          call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
    271           call calcpar(memind(2),uuh,vvh,pvh,metdata_format)
    272           call calcpar_nests(memind(2),uuhn,vvhn,pvhn,metdata_format)
    273           if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    274             call verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
    275           else
    276             call verttransform_gfs(memind(2),uuh,vvh,wwh,pvh)
    277           end if
     244          call calcpar(memind(2),uuh,vvh,pvh)
     245          call calcpar_nests(memind(2),uuhn,vvhn,pvhn)
     246          call verttransform(memind(2),uuh,vvh,wwh,pvh)
    278247          call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
    279248        end if
  • src/gridcheck_gfs.f90

    rd8eed02 r4c64400  
    2020!**********************************************************************
    2121
    22 subroutine gridcheck_gfs
     22subroutine gridcheck
    2323
    2424  !**********************************************************************
     
    3838  !             CHANGE: 03/12/2008, Harald Sodemann, update to f90 with *
    3939  !                                 ECMWF grib_api                      *
    40   !                                                                     *
    41   !   Unified ECMWF and GFS builds                                      *
    42   !   Marian Harustak, 12.5.2017                                        *
    43   !     - Renamed routine from gridcheck to gridcheck_gfs               *
    4440  !                                                                     *
    4541  !**********************************************************************
     
    231227       yaux2in,iret)
    232228  call grib_check(iret,gribFunction,gribErrorMsg)
    233 
    234   ! Fix for flexpart.eu ticket #48
    235   if (xaux2in.lt.0) xaux2in = 359.0
    236229
    237230  xaux1=xaux1in
     
    544537  endif
    545538
    546 end subroutine gridcheck_gfs
     539end subroutine gridcheck
  • src/makefile

    rd8eed02 rd1a8707  
    1212#       'make -j ecmwf gcc=4.9',
    1313#    also set environment variable LD_LIBRARY_PATH to point to compiler libraries
    14 #
    15 #    Makefile was modified to produce unified executable for both ECMWF and GFS meteo data formats
    16 #    gributils were included to detect format of meteo data
    17 #
    18 #    Cpp directives USE_MPIINPLACE were added to three source files. The effect of these directives
    19 #    are to enable the MPI_IN_PLACE option only if compiled with a -DUSE_MPIINPLACE directive.
    20 #    Otherwise, a safer option (which requires the allocation of another array) is used by default.
    21 #    In makefile added the -x f95-cpp-input flag for compiling of cpp directives.
    2214#
    2315#  USAGE
    24 #    Compile serial FLEXPART
    25 #      make [-j] serial
    26 #
    27 #    Compile parallel FLEXPART
    28 #      make [-j] mpi
     16#    Compile serial FLEXPART (ECMWF)
     17#      make [-j] ecmwf
     18#
     19#    Compile parallel FLEXPART (ECMWF)
     20#      make [-j] ecmwf-mpi
    2921#     
    30 #    Compile for debugging parallel FLEXPART
    31 #      make [-j] mpi-dbg
     22#    Compile for debugging parallel FLEXPART (ECMWF)
     23#      make [-j] ecmwf-mpi-dbg
     24#
     25#    Compile serial FLEXPART (GFS)
     26#      make [-j] gfs
     27#
     28#    Compile parallel FLEXPART (GFS)
     29#      make [-j] gfs-mpi
    3230#
    3331################################################################################
    3432
    3533## PROGRAMS
    36 # Unified executable names
    37 # The same executable is used for both ECMWF and GFS metdata
    38 
    39 # Parallel processing executable
    40 FLEXPART-MPI = FLEXPART_MPI
    41 
    42 # Parallel processing executable with debugging info
    43 FLEXPART-MPI-DBG = DBG_FLEXPART_MPI
    44 
    45 # Serial processing executable
    46 FLEXPART-SERIAL = FLEXPART
    47 
     34FLEXPART-ECMWF-MPI      = FP_ecmwf_MPI
     35FLEXPART-ECMWF-MPI-DBG  = DBG_FP_ecmwf_MPI
     36FLEXPART-ECMWF          = FP_ecmwf_gfortran
     37FLEXPART-GFS            = FP_gfs_gfortran
     38FLEXPART-GFS-MPI        = FP_gfs_MPI
    4839
    4940ifeq ($(gcc), 4.9)
     
    7061
    7162
    72 # path to gributils used to detect meteodata format
    73 VPATH = gributils/
    74 
    75 
    7663## OPTIMIZATION LEVEL
    7764O_LEV = 2 # [0,1,2,3,g,s,fast]
     
    8168LIBS = -lgrib_api_f90 -lgrib_api -lm -ljasper -lnetcdff # -fopenmp
    8269
    83 FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -g -cpp -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(FUSER)  #-Warray-bounds -fcheck=all # -march=native
    84 
    85 DBGFLAGS = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV_DBG) -g3 -ggdb3 -cpp -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV_DBG) -fbacktrace   -Wall  -fdump-core $(FUSER)  #  -ffpe-trap=invalid,overflow,denormal,underflow,zero  -Warray-bounds -fcheck=all
    86 
    87 LDFLAGS  = $(FFLAGS) -L$(LIBPATH1) -Wl,-rpath,$(LIBPATH1) $(LIBS) #-L$(LIBPATH2)
     70FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -g -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(FUSER)  #-Warray-bounds -fcheck=all # -march=native
     71
     72DBGFLAGS = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV_DBG) -g3 -ggdb3 -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV_DBG) -fbacktrace   -Wall  -fdump-core $(FUSER)  #  -ffpe-trap=invalid,overflow,denormal,underflow,zero  -Warray-bounds -fcheck=all
     73
     74LDFLAGS  = $(FFLAGS) -L$(LIBPATH1) $(LIBS) #-L$(LIBPATH2)
    8875LDDEBUG  = $(DBGFLAGS) -L$(LIBPATH1) $(LIBS) #-L$(LIBPATH2)
    8976
     
    9582xmass_mod.o             flux_mod.o \
    9683point_mod.o             outg_mod.o \
    97 mean_mod.o              random_mod.o \
    98 class_gribfile_mod.o
     84mean_mod.o              random_mod.o
    9985
    10086MPI_MODOBJS = \
     
    11399        redist.o                \
    114100        concoutput_surf.o       concoutput_surf_nest.o  \
    115         getfields.o \
    116         readwind_ecmwf.o
     101        getfields.o
    117102
    118103## For MPI version
     
    127112        redist_mpi.o            \
    128113        concoutput_surf_mpi.o   concoutput_surf_nest_mpi.o      \
    129         getfields_mpi.o \
    130         readwind_ecmwf_mpi.o
     114        getfields_mpi.o
     115
     116### WINDFIELDS
     117## For ECMWF (serial) version:
     118OBJECTS_ECMWF = \
     119        calcpar.o          readwind.o \
     120        richardson.o       verttransform.o \
     121        obukhov.o          gridcheck.o  \
     122        convmix.o          calcmatrix.o \
     123        ecmwf_mod.o
     124
     125
     126## For ECMWF MPI version:
     127OBJECTS_ECMWF_MPI = \
     128        gridcheck.o        readwind_mpi.o \
     129        calcpar.o          \
     130        richardson.o       verttransform.o \
     131        obukhov.o          \
     132        convmix.o          calcmatrix.o \
     133        ecmwf_mod.o
     134
     135## For GFS (serial) version:
     136OBJECTS_GFS = \
     137        calcpar_gfs.o          readwind_gfs.o \
     138        richardson_gfs.o       verttransform_gfs.o \
     139        obukhov_gfs.o          gridcheck_gfs.o  \
     140        convmix_gfs.o          calcmatrix_gfs.o \
     141        gfs_mod.o
    131142
    132143OBJECTS = \
     
    143154ew.o                    readreleases.o  \
    144155readdepo.o              get_vdep_prob.o   \
    145 get_wetscav.o           readwind_gfs.o \
     156get_wetscav.o   \
    146157psim.o                  outgrid_init.o  \
    147 outgrid_init_nest.o     calcmatrix.o \
     158outgrid_init_nest.o     \
    148159photo_O1D.o             readlanduse.o \
    149160interpol_wind.o         readoutgrid.o \
    150161interpol_all.o          readpaths.o \
    151 getrb.o                 obukhov.o \
    152 getrc.o                 convmix.o \
     162getrb.o                 \
     163getrc.o                 \
    153164getvdep.o               readspecies.o \
    154 interpol_misslev.o      richardson.o \
    155 scalev.o                verttransform_ecmwf.o \
    156 pbl_profile.o           readOHfield.o \
    157 juldate.o               verttransform_gfs.o \
     165interpol_misslev.o      \
     166scalev.o \
     167pbl_profile.o           readOHfield.o\
     168juldate.o               \
    158169interpol_vdep.o         interpol_rain.o \
    159170hanna.o                 wetdepokernel.o \
    160 calcpar.o               wetdepo.o \
     171                  wetdepo.o \
    161172hanna_short.o           windalign.o \
    162 hanna1.o                gridcheck_ecmwf.o \
    163 gridcheck_gfs.o         gridcheck_nests.o \
     173hanna1.o                        \
     174                        gridcheck_nests.o \
    164175readwind_nests.o        calcpar_nests.o \
    165176verttransform_nests.o   interpol_all_nests.o \
    166177interpol_wind_nests.o   interpol_misslev_nests.o \
    167178interpol_vdep_nests.o   interpol_rain_nests.o \
    168 readageclasses.o        detectformat.o \
     179readageclasses.o        \
    169180calcfluxes.o            fluxoutput.o \
    170181qvsat.o                 skplin.o \
     
    190201%.o: %.mod
    191202
    192 # serial executable
    193 serial: $(FLEXPART-SERIAL)
    194 serial: FC := $(F90)
    195 
    196 # parallel processing executable
    197 mpi: $(FLEXPART-MPI)
    198 mpi: FC := $(MPIF90)
    199 
    200 # parallel processing with debugging info
    201 mpi-dbg: $(FLEXPART-MPI-DBG)
    202 mpi-dbg: FFLAGS := $(DBGFLAGS)
    203 mpi-dbg: LDFLAGS:= $(LDDEBUG)
    204 mpi-dbg: FC := $(MPIF90)
    205 
    206 $(FLEXPART-SERIAL): $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL)
    207         +$(FC) -o $@ $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL) $(LDFLAGS)
    208 
    209 $(FLEXPART-MPI): $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI)
     203ecmwf: $(FLEXPART-ECMWF)
     204ecmwf: FC := $(F90)
     205
     206ecmwf-mpi: $(FLEXPART-ECMWF-MPI)
     207ecmwf-mpi: FC := $(MPIF90)
     208
     209ecmwf-mpi-dbg: $(FLEXPART-ECMWF-MPI-DBG)
     210ecmwf-mpi-dbg: FFLAGS := $(DBGFLAGS)
     211ecmwf-mpi-dbg: LDFLAGS:= $(LDDEBUG)
     212ecmwf-mpi-dbg: FC := $(MPIF90)
     213
     214gfs: $(FLEXPART-GFS)
     215gfs: FC := $(F90)
     216
     217gfs-mpi: $(FLEXPART-GFS-MPI)
     218gfs-mpi: FC := $(MPIF90)
     219
     220#all: $(FLEXPART-ECMWF)
     221#all: $(FLEXPART-ECMWF-MPI)
     222
     223## This allows for switching between ECMWF/GFS without editing source code.
     224wind_mod = ecmwf_mod.o # default wind
     225# ifeq ($(MAKECMDGOALS),ecmwf)
     226# wind_mod = ecmwf_mod.o
     227# endif
     228# ifeq ($(MAKECMDGOALS),ecmwf-mpi)
     229# wind_mod = ecmwf_mod.o
     230# endif
     231# ifeq ($(MAKECMDGOALS),ecmwf-mpi-dbg)
     232# wind_mod = ecmwf_mod.o
     233# endif
     234
     235ifeq ($(MAKECMDGOALS),gfs)
     236wind_mod = gfs_mod.o
     237endif
     238ifeq ($(MAKECMDGOALS),gfs-mpi)
     239wind_mod = gfs_mod.o
     240endif
     241
     242$(FLEXPART-ECMWF): $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL) $(OBJECTS_ECMWF)
     243        +$(FC) -o $@ $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL) $(OBJECTS_ECMWF) $(LDFLAGS)
     244
     245$(FLEXPART-ECMWF-MPI): $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) $(OBJECTS_ECMWF_MPI)
    210246        +$(FC) -o $@ $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) \
    211         $(LDFLAGS)
    212 
    213 $(FLEXPART-MPI-DBG): $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI)
     247        $(OBJECTS_ECMWF_MPI) $(LDFLAGS)
     248#       +$(FC) -o $@ *.o $(LDFLAGS)
     249
     250$(FLEXPART-ECMWF-MPI-DBG): $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) \
     251        $(OBJECTS_ECMWF_MPI)
    214252        +$(FC) -o $@ $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) \
    215         $(LDFLAGS)
     253        $(OBJECTS_ECMWF_MPI) $(LDFLAGS)
     254
     255$(FLEXPART-GFS): $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL) $(OBJECTS_GFS)
     256        +$(FC) -o $@ $(MODOBJS) $(OBJECTS) $(OBJECTS_SERIAL) $(OBJECTS_GFS) $(LDFLAGS)
     257
     258$(FLEXPART-GFS-MPI): $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) $(OBJECTS_GFS)
     259        +$(FC) -o $@ $(MODOBJS) $(MPI_MODOBJS) $(OBJECTS) $(OBJECTS_MPI) \
     260        $(OBJECTS_GFS) $(LDFLAGS)
    216261
    217262%.o: %.f90
     
    222267
    223268cleanall:
    224         \rm -f *.o *.mod $(FLEXPART-MPI) $(FLEXPART-MPI-DBG) $(FLEXPART-SERIAL)
    225 
     269        \rm -f *.o *.mod $(FLEXPART-ECMWF-MPI) $(FLEXPART-ECMWF-MPI-DBG) $(FLEXPART-ECMWF) \
     270        $(FLEXPART-GFS-MPI) $(FLEXPART-GFS)
    226271
    227272.SUFFIXES = $(SUFFIXES) .f90
     
    237282        random_mod.o
    238283calcfluxes.o: com_mod.o flux_mod.o outg_mod.o par_mod.o
    239 calcmatrix.o: com_mod.o conv_mod.o par_mod.o class_gribfile_mod.o
    240 calcpar.o: com_mod.o par_mod.o class_gribfile_mod.o
     284calcmatrix.o: com_mod.o conv_mod.o par_mod.o
     285calcmatrix_gfs.o: com_mod.o conv_mod.o par_mod.o
     286calcpar.o: com_mod.o par_mod.o
     287calcpar_gfs.o: com_mod.o par_mod.o
    241288calcpar_nests.o: com_mod.o par_mod.o
    242289calcpv.o: com_mod.o par_mod.o
     
    264311conv_mod.o: par_mod.o
    265312convect43c.o: conv_mod.o par_mod.o
    266 convmix.o: com_mod.o conv_mod.o flux_mod.o par_mod.o class_gribfile_mod.o
     313convmix.o: com_mod.o conv_mod.o flux_mod.o par_mod.o
     314convmix_gfs.o: com_mod.o conv_mod.o par_mod.o
    267315coordtrafo.o: com_mod.o par_mod.o point_mod.o
    268 detectformat.o: com_mod.o par_mod.o class_gribfile_mod.o
    269316distance.o: par_mod.o
    270317distance2.o: par_mod.o
     
    272319drydepokernel_nest.o: com_mod.o par_mod.o unc_mod.o
    273320erf.o: par_mod.o
    274 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
     321FLEXPART.o: com_mod.o conv_mod.o par_mod.o point_mod.o random_mod.o netcdf_output_mod.o
    275322FLEXPART_MPI.o: com_mod.o conv_mod.o mpi_mod.o par_mod.o point_mod.o \
    276         random_mod.o netcdf_output_mod.o class_gribfile_mod.o
     323        random_mod.o netcdf_output_mod.o
    277324fluxoutput.o: com_mod.o flux_mod.o outg_mod.o par_mod.o
    278325get_settling.o: com_mod.o par_mod.o
    279 getfields.o: com_mod.o par_mod.o class_gribfile_mod.o
    280 getfields_mpi.o: com_mod.o par_mod.o mpi_mod.o class_gribfile_mod.o
     326getfields.o: com_mod.o par_mod.o
     327getfields_mpi.o: com_mod.o par_mod.o mpi_mod.o
    281328gethourlyOH.o: com_mod.o oh_mod.o par_mod.o
    282329getrb.o: par_mod.o
     
    284331getvdep.o: com_mod.o par_mod.o
    285332getvdep_nests.o: com_mod.o par_mod.o
    286 gridcheck_ecmwf.o: cmapf_mod.o com_mod.o conv_mod.o par_mod.o
     333gridcheck.o: cmapf_mod.o com_mod.o conv_mod.o par_mod.o
    287334gridcheck_emos.o: com_mod.o conv_mod.o par_mod.o
    288335gridcheck_fnl.o: cmapf_mod.o com_mod.o conv_mod.o par_mod.o
     
    319366mpi_mod.o: com_mod.o par_mod.o unc_mod.o
    320367netcdf_output_mod.o: com_mod.o outg_mod.o par_mod.o point_mod.o unc_mod.o mean_mod.o
    321 obukhov.o: par_mod.o class_gribfile_mod.o
     368obukhov.o: par_mod.o
     369obukhov_gfs.o: par_mod.o
    322370ohreaction.o: com_mod.o oh_mod.o par_mod.o
    323371openouttraj.o: com_mod.o par_mod.o point_mod.o
     
    326374outgrid_init.o: com_mod.o flux_mod.o oh_mod.o outg_mod.o par_mod.o unc_mod.o
    327375outgrid_init_nest.o: com_mod.o outg_mod.o par_mod.o unc_mod.o
     376par_mod.o : $(wind_mod)
    328377part0.o: par_mod.o
    329378partdep.o: par_mod.o
     
    353402readreleases.o: com_mod.o par_mod.o point_mod.o xmass_mod.o
    354403readspecies.o: com_mod.o par_mod.o
    355 readwind_ecmwf.o: com_mod.o par_mod.o
     404readwind.o: com_mod.o par_mod.o
    356405readwind_emos.o: com_mod.o par_mod.o
    357406readwind_gfs.o: com_mod.o par_mod.o
    358407readwind_gfs_emos.o: com_mod.o par_mod.o
    359 readwind_ecmwf_mpi.o: com_mod.o mpi_mod.o par_mod.o
     408readwind_mpi.o: com_mod.o mpi_mod.o par_mod.o
    360409readwind_nests.o: com_mod.o par_mod.o
    361410readwind_nests_emos.o: com_mod.o par_mod.o
     
    366415releaseparticles_mpi.o: com_mod.o mpi_mod.o par_mod.o point_mod.o \
    367416        random_mod.o xmass_mod.o
    368 richardson.o: par_mod.o class_gribfile_mod.o
     417richardson.o: par_mod.o
     418richardson_gfs.o: par_mod.o
    369419scalev.o: par_mod.o
    370420shift_field.o: par_mod.o
     
    375425        par_mod.o point_mod.o unc_mod.o xmass_mod.o netcdf_output_mod.o
    376426unc_mod.o: par_mod.o
    377 verttransform_ecmwf.o: cmapf_mod.o com_mod.o par_mod.o
     427verttransform.o: cmapf_mod.o com_mod.o par_mod.o
    378428verttransform_gfs.o: cmapf_mod.o com_mod.o par_mod.o
    379429verttransform_nests.o: com_mod.o par_mod.o
  • src/mpi_mod.f90

    r6ecb30a raa8c34a  
    5959!                                                                            *
    6060!*****************************************************************************
    61 !                                                                            *
    62 ! Modification by DJM, 2017-05-09 - added #ifdef USE_MPIINPLACE cpp          *
    63 ! directive to mpif_tm_reduce_grid() to insure that MPI_IN_PLACE is          *
    64 ! used in the MPI_Reduce() only if specifically compiled with that           *
    65 ! directive.                                                                 *
    66 !                                                                            *
    67 !*****************************************************************************
    6861
    6962  use mpi
     
    24322425
    24332426! 2) Using in-place reduction
    2434 
    2435 !!!--------------------------------------------------------------------
    2436 !!! DJM - 2017-05-09 change - MPI_IN_PLACE option for MPI_Reduce() causes
    2437 !!! severe numerical problems in some cases.  I'm guessing there are memory
    2438 !!! overrun issues in this complex code, but have so far failed to identify
    2439 !!! a specific problem.  And/or, when one searches the Internet for this
    2440 !!! issue, there is "some" hint that the implementation may be buggy. 
    2441 !!!
    2442 !!! At this point, with the following CPP USE_MPIINPLACE directive, the
    2443 !!! default behaviour will be to not use the MPI_IN_PLACE option.
    2444 !!! Users will have to compile with -DUSE_MPIINPLACE if they want that option.
    2445 !!! Introduction of the CPP directives also requires that the code be compiled
    2446 !!! with the "-x f95-cpp-input" option.
    2447 !!!
    2448 !!! Modification of this section requires the addition of array gridunc0, which
    2449 !!! requires an allocation in outgrid_init.f90 and initial declaration in
    2450 !!! unc_mod.f90.
    2451 !!!--------------------------------------------------------------------
    2452 
    2453 #ifdef USE_MPIINPLACE
    2454 
    24552427    if (lroot) then
    24562428      call MPI_Reduce(MPI_IN_PLACE, gridunc, grid_size3d, mp_sp, MPI_SUM, id_root, &
     
    24612433           & mp_comm_used, mp_ierr)
    24622434    end if
    2463 
    2464 #else
    2465 
    2466       call MPI_Reduce(gridunc, gridunc0, grid_size3d, mp_sp, MPI_SUM, id_root, &
    2467            & mp_comm_used, mp_ierr)
    2468       if (lroot) gridunc = gridunc0
    2469 
    2470 #endif
    24712435
    24722436    if ((WETDEP).and.(ldirect.gt.0)) then
  • src/obukhov.f90

    r6ecb30a re200b7a  
    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)
    2323
    2424  !********************************************************************
     
    2727  !                       Date:   1994-06-27                          *
    2828  !                                                                   *
    29   !     This program calculates Obukhov scale height from surface     *
    30   !     meteorological data and sensible heat flux.                   *
     29  !  Update: A. Stohl, 2000-09-25, avoid division by zero by          *
     30  !  setting ustar to minimum value                                   *
    3131  !                                                                   *
    3232  !********************************************************************
    3333  !                                                                   *
    34   !  Update: A. Stohl, 2000-09-25, avoid division by zero by          *
    35   !  setting ustar to minimum value                                   *
    36   !  CHANGE: 17/11/2005 Caroline Forster NCEP GFS version             *
    37   !                                                                   *
    38   !   Unified ECMWF and GFS builds                                    *
    39   !   Marian Harustak, 12.5.2017                                      *
    40   !     - Merged obukhov and obukhov_gfs into one routine using       *
    41   !       if-then for meteo-type dependent code                       *
     34  !     This program calculates Obukhov scale height from surface     *
     35  !     meteorological data and sensible heat flux.                   *
    4236  !                                                                   *
    4337  !********************************************************************
     
    5347  !     akm     ECMWF vertical discretization parameter               *
    5448  !     bkm     ECMWF vertical discretization parameter               *
    55   !     plev                                                          *
    56   !     metdata_format format of metdata (ecmwf/gfs)                  *
    5749  !                                                                   *
    5850  !********************************************************************
    5951
    6052  use par_mod
    61   use class_gribfile
    6253
    6354  implicit none
    6455
    65   integer :: metdata_format
    6656  real :: akm(nwzmax),bkm(nwzmax)
    6757  real :: ps,tsurf,tdsurf,tlev,ustar,hf,e,ew,tv,rhoa,plev
     
    7262  tv=tsurf*(1.+0.378*e/ps)               ! virtual temperature
    7363  rhoa=ps/(r_air*tv)                      ! air density
    74   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    7564  ak1=(akm(1)+akm(2))/2.
    7665  bk1=(bkm(1)+bkm(2))/2.
    7766  plev=ak1+bk1*ps                        ! Pressure level 1
    78   end if
    7967  theta=tlev*(100000./plev)**(r_air/cpa) ! potential temperature
    8068  if (ustar.le.0.) ustar=1.e-8
  • src/outgrid_init.f90

    r6ecb30a r6b22af9  
    1919! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
    2020!**********************************************************************
    21 !                                                                     *
    22 ! DJM - 2017-05-09 - added #ifdef USE_MPIINPLACE cpp directive to     *
    23 ! enable allocation of a gridunc0 array if required by MPI code in    *
    24 ! mpi_mod.f90                                                         *
    25 !                                                                     *
    26 !**********************************************************************
    27 
    2821
    2922subroutine outgrid_init
     
    222215! Extra field for totals at MPI root process
    223216  if (lroot.and.mpi_mode.gt.0) then
    224 
    225 #ifdef USE_MPIINPLACE
    226 #else
    227     ! If MPI_IN_PLACE option is not used in mpi_mod.f90::mpif_tm_reduce_grid(),
    228     ! then an aux array is needed for parallel grid reduction
    229     allocate(gridunc0(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec, &
    230          maxpointspec_act,nclassunc,maxageclass),stat=stat)
    231     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc0'
    232 #endif
     217    ! allocate(gridunc0(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec, &
     218    !      maxpointspec_act,nclassunc,maxageclass),stat=stat)
     219    ! if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc0'
    233220    if (ldirect.gt.0) then
    234221      allocate(wetgridunc0(0:numxgrid-1,0:numygrid-1,maxspec, &
  • src/par_mod.f90

    rd8eed02 rd1a8707  
    3737
    3838module par_mod
     39
     40!************************************************************************
     41! wind_mod: is gfs_mod.f90 for target gfs, ecmwf_mod.f90 for target ecmwf
     42!************************************************************************
     43  use wind_mod
    3944
    4045  implicit none
     
    141146  !*********************************************
    142147 
    143 !  integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !ECMWF new
    144   integer,parameter :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138 !ECMWF new
    145 
    146 !  integer,parameter :: nxmax=181,nymax=91,nuvzmax=138,nwzmax=138,nzmax=138 !ECMWF new
    147 
    148 !  INTEGER,PARAMETER :: nxmax=361,nymax=181,nuvzmax=138,nwzmax=138,nzmax=138 !NCEP data
    149 
    150 !  integer,parameter :: nxshift=359  ! for ECMWF
    151   integer,parameter :: nxshift=0     ! for GFS
    152 
    153   !*********************************************
    154   ! Maximum dimensions of the nested input grids
    155   !*********************************************
    156 
    157   integer,parameter :: maxnests=1,nxmaxn=451,nymaxn=226
    158 
    159   ! nxmax,nymax        maximum dimension of wind fields in x and y
    160   !                    direction, respectively
    161   ! nuvzmax,nwzmax     maximum dimension of (u,v) and (w) wind fields in z
    162   !                    direction (for fields on eta levels)
    163   ! nzmax              maximum dimension of wind fields in z direction
    164   !                    for the transformed Cartesian coordinates
    165   ! nxshift            for global grids (in x), the grid can be shifted by
    166   !                    nxshift grid points, in order to accomodate nested
    167   !                    grids, and output grids overlapping the domain "boundary"
    168   !                    nxshift must not be negative; "normal" setting would be 0
    169 
     148  ! Moved to ecmwf_mod.f90 (for ECMWF) / gfs_mod.f90 (for GFS)
    170149 
    171150  integer,parameter :: nconvlevmax = nuvzmax-1
     
    290269  integer,parameter ::  icmv=-9999
    291270
     271! Parameters for testing
     272!*******************************************
     273!  integer :: verbosity=0
    292274
    293275end module par_mod
  • src/readwind_gfs.f90

    r6ecb30a r8a65cb0  
    2020!**********************************************************************
    2121
    22 subroutine readwind_gfs(indj,n,uuh,vvh,wwh)
     22subroutine readwind(indj,n,uuh,vvh,wwh)
    2323
    2424  !***********************************************************************
     
    3838  !*             CHANGE: 03/12/2008, Harald Sodemann, update to f90 with *
    3939  !*                                 ECMWF grib_api                      *
    40   !                                                                      *
    41   !   Unified ECMWF and GFS builds                                       *
    42   !   Marian Harustak, 12.5.2017                                         *
    43   !     - Renamed routine from readwind to readwind_gfs                  *
    4440  !*                                                                     *
    4541  !***********************************************************************
     
    720716  stop 'Execution terminated'
    721717
    722 end subroutine readwind_gfs
     718end subroutine readwind
  • src/richardson.f90

    r6ecb30a rc2162ce  
    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)
    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   !                                                                           *
    4543  !     Update: 1999-02-01 by G. Wotawa                                       *
    4644  !                                                                           *
     
    4846  !     instead of first model level.                                         *
    4947  !     New input variables tt2, td2 introduced.                              *
    50   !                                                                           *
    51   !     CHANGE: 17/11/2005 Caroline Forster NCEP GFS version                  *
    52   !                                                                           *
    53   !     Unified ECMWF and GFS builds                                          *
    54   !     Marian Harustak, 12.5.2017                                            *
    55   !       - Merged richardson and richardson_gfs into one routine using       *
    56   !         if-then for meteo-type dependent code                             *
    5748  !                                                                           *
    5849  !****************************************************************************
     
    6455  ! tv                         virtual temperature                            *
    6556  ! wst                        convective velocity scale                      *
    66   ! metdata_format             format of metdata (ecmwf/gfs)                  *
    6757  !                                                                           *
    6858  ! Constants:                                                                *
     
    7262
    7363  use par_mod
    74   use class_gribfile
    7564
    7665  implicit none
    7766
    78   integer :: metdata_format
    79   integer :: i,k,nuvz,iter,llev,loop_start
     67  integer :: i,k,nuvz,iter
    8068  real :: tv,tvold,zref,z,zold,pint,pold,theta,thetaref,ri
    8169  real :: akz(nuvz),bkz(nuvz),ulev(nuvz),vlev(nuvz),hf,wst,tt2,td2,ew
     
    8876  excess=0.0
    8977  iter=0
    90 
    91   if (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
    92     ! NCEP version: find first model level above ground
    93     !**************************************************
    94 
    95      llev = 0
    96      do i=1,nuvz
    97        if (psurf.lt.akz(i)) llev=i
    98      end do
    99      llev = llev+1
    100     ! sec llev should not be 1!
    101      if (llev.eq.1) llev = 2
    102      if (llev.gt.nuvz) llev = nuvz-1
    103     ! NCEP version
    104   end if
    105 
    10678
    10779  ! Compute virtual temperature and virtual potential temperature at
     
    12395  ! Integrate z up to one level above zt
    12496  !*************************************
    125   if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
    126     loop_start=2
    127   else
    128     loop_start=llev
    129   end if
    130   do k=loop_start,nuvz
     97
     98  do k=2,nuvz
    13199    pint=akz(k)+bkz(k)*psurf  ! pressure on model layers
    132100    tv=ttlev(k)*(1.+0.608*qvlev(k))
  • src/timemanager.f90

    r6ecb30a ra76d954  
    2020!**********************************************************************
    2121
    22 subroutine timemanager(metdata_format)
     22subroutine timemanager
    2323
    2424  !*****************************************************************************
     
    5050  !   For compatibility with MPI version,                                      *
    5151  !   variables uap,ucp,uzp,us,vs,ws,cbt now in module com_mod                 *
    52   !  Unified ECMWF and GFS builds                                              *
    53   !   Marian Harustak, 12.5.2017                                               *
    54   !   - Added passing of metdata_format as it was needed by called routines    *
    5552  !*****************************************************************************
    5653  !                                                                            *
     
    8683  ! xtra1(maxpart), ytra1(maxpart), ztra1(maxpart) =                           *
    8784  !                    spatial positions of trajectories                       *
    88   ! metdata_format     format of metdata (ecmwf/gfs)                           *
    8985  !                                                                            *
    9086  ! Constants:                                                                 *
     
    106102  implicit none
    107103
    108   integer :: metdata_format
    109104  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1
    110105! integer :: ksp
     
    199194           write (*,*) 'timemanager> call convmix -- backward'
    200195        endif         
    201       call convmix(itime,metdata_format)
     196      call convmix(itime)
    202197        if (verbosity.gt.1) then
    203198          !CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     
    212207           write (*,*) 'timemanager> call getfields'
    213208    endif
    214     call getfields(itime,nstop1,metdata_format)
     209    call getfields(itime,nstop1)
    215210        if (verbosity.gt.1) then
    216211          CALL SYSTEM_CLOCK(count_clock)
     
    271266       write (*,*) 'timemanager> call convmix -- forward'
    272267     endif   
    273      call convmix(itime,metdata_format)
     268     call convmix(itime)
    274269   endif
    275270
  • src/timemanager_mpi.f90

    rd8eed02 rb5127f9  
    2020!**********************************************************************
    2121
    22 subroutine timemanager(metdata_format)
     22subroutine timemanager
    2323
    2424!*****************************************************************************
     
    5050!   MPI version                                                              *
    5151!   Variables uap,ucp,uzp,us,vs,ws,cbt now in module com_mod                 *
    52 !  Unified ECMWF and GFS builds                                              *
    53 !   Marian Harustak, 12.5.2017                                               *
    54 !   - Added passing of metdata_format as it was needed by called routines    *
    5552!*****************************************************************************
    5653!                                                                            *
     
    8683! xtra1(maxpart), ytra1(maxpart), ztra1(maxpart) =                           *
    8784!                    spatial positions of trajectories                       *
    88 ! metdata_format     format of metdata (ecmwf/gfs)                           *
    8985!                                                                            *
    9086! Constants:                                                                 *
     
    107103  implicit none
    108104
    109   integer :: metdata_format
    110105  logical :: reqv_state=.false. ! .true. if waiting for a MPI_Irecv to complete
    111106  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1,memstat=0
     
    210205      endif
    211206! readwind process skips this step
    212       if (.not.(lmpreader.and.lmp_use_reader)) call convmix(itime,metdata_format)
     207      if (.not.(lmpreader.and.lmp_use_reader)) call convmix(itime)
    213208    endif
    214209
     
    223218    if (mp_measure_time) call mpif_mtime('getfields',0)
    224219
    225     call getfields(itime,nstop1,memstat,metdata_format)
     220    call getfields(itime,nstop1,memstat)
    226221
    227222    if (mp_measure_time) call mpif_mtime('getfields',1)
     
    351346        write (*,*) 'timemanager> call convmix -- forward'
    352347      endif
    353       call convmix(itime,metdata_format)
     348      call convmix(itime)
    354349    endif
    355350
  • src/unc_mod.f90

    r6ecb30a r4c64400  
    1919! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
    2020!**********************************************************************
    21 !                                                                     *
    22 ! DJM - 2017-05-09 - added #ifdef USE_MPIINPLACE cpp directive to     *
    23 ! enable declaration of a gridunc0 array if required by MPI code in   *
    24 ! mpi_mod.f90                                                         *
    25 !                                                                     *
    26 !**********************************************************************
    2721
    2822module unc_mod
     
    3327
    3428  real,allocatable, dimension (:,:,:,:,:,:,:) :: gridunc
    35 #ifdef USE_MPIINPLACE
    36 #else
    37   ! If MPI_IN_PLACE option is not used in mpi_mod.f90::mpif_tm_reduce_grid(),
    38   ! then an aux array is needed for parallel grid reduction
    39   real,allocatable, dimension (:,:,:,:,:,:,:) :: gridunc0
    40 #endif
    4129  real,allocatable, dimension (:,:,:,:,:,:,:) :: griduncn
    4230  real(dep_prec),allocatable, dimension (:,:,:,:,:,:) :: drygridunc
  • src/verttransform_gfs.f90

    r6ecb30a r4fbe7a5  
    2020!**********************************************************************
    2121
    22 subroutine verttransform_gfs(n,uuh,vvh,wwh,pvh)
     22subroutine verttransform(n,uuh,vvh,wwh,pvh)
    2323  !                      i  i   i   i   i
    2424  !*****************************************************************************
     
    4747  !  Changes, Bernd C. Krueger, Feb. 2001:
    4848  !   Variables tth and qvh (on eta coordinates) from common block
    49   !
    50   !   Unified ECMWF and GFS builds                                     
    51   !   Marian Harustak, 12.5.2017                                       
    52   !     - Renamed routine from verttransform to verttransform_gfs
    53   !
    5449  !*****************************************************************************
    5550  !                                                                            *
     
    536531
    537532
    538 end subroutine verttransform_gfs
     533end subroutine verttransform
  • src/writeheader.f90

    r6ecb30a rf13406c  
    3535  !*****************************************************************************
    3636  !                                                                            *
    37   !  Modified to remove TRIM around the output of flexversion so that          *
    38   !  it will be a constant length (defined in com_mod.f90) in output header    *
    39   !                                                                            *
    40   !     Don Morton, Boreal Scientific Computing                                *
    41   !     07 May 2017                                                            *
    42   !                                                                            *
    43   !*****************************************************************************
    44   !                                                                            *
    4537  ! Variables:                                                                 *
    4638  !                                                                            *
     
    7567
    7668  if (ldirect.eq.1) then
    77     write(unitheader) ibdate,ibtime, flexversion
     69    write(unitheader) ibdate,ibtime, trim(flexversion)
    7870  else
    79     write(unitheader) iedate,ietime, flexversion
     71    write(unitheader) iedate,ietime, trim(flexversion)
    8072  endif
    8173
  • src/writeheader_nest.f90

    r6ecb30a r4fbe7a5  
    3535  !*****************************************************************************
    3636  !                                                                            *
    37   !  Modified to remove TRIM around the output of flexversion so that          *
    38   !  it will be a constant length (defined in com_mod.f90) in output header    *
    39   !                                                                            *
    40   !     Don Morton, Boreal Scientific Computing                                *
    41   !     07 May 2017                                                            *
    42   !                                                                            *
    43   !*****************************************************************************
    44   !                                                                            *
    4537  ! Variables:                                                                 *
    4638  !                                                                            *
     
    7567
    7668  if (ldirect.eq.1) then
    77     write(unitheader) ibdate,ibtime, flexversion
     69    write(unitheader) ibdate,ibtime, trim(flexversion)
    7870  else
    79     write(unitheader) iedate,ietime, flexversion
     71    write(unitheader) iedate,ietime, trim(flexversion)
    8072  endif
    8173
  • src/writeheader_nest_surf.f90

    r6ecb30a rf13406c  
    3535  !*****************************************************************************
    3636  !                                                                            *
    37   !  Modified to remove TRIM around the output of flexversion so that          *
    38   !  it will be a constant length (defined in com_mod.f90) in output header    *
    39   !                                                                            *
    40   !     Don Morton, Boreal Scientific Computing                                *
    41   !     07 May 2017                                                            *
    42   !                                                                            *
    43   !*****************************************************************************
    44   !                                                                            *
    4537  ! Variables:                                                                 *
    4638  !                                                                            *
     
    7567
    7668  if (ldirect.eq.1) then
    77     write(unitheader) ibdate,ibtime,flexversion
     69    write(unitheader) ibdate,ibtime,trim(flexversion)
    7870  else
    79     write(unitheader) iedate,ietime,flexversion
     71    write(unitheader) iedate,ietime,trim(flexversion)
    8072  endif
    8173
  • src/writeheader_surf.f90

    r6ecb30a rf13406c  
    3535  !*****************************************************************************
    3636  !                                                                            *
    37   !  Modified to remove TRIM around the output of flexversion so that          *
    38   !  it will be a constant length (defined in com_mod.f90) in output header    *
    39   !                                                                            *
    40   !     Don Morton, Boreal Scientific Computing                                *
    41   !     07 May 2017                                                            *
    42   !                                                                            *
    43   !*****************************************************************************
    44   !                                                                            *
    4537  ! Variables:                                                                 *
    4638  !                                                                            *
     
    7567
    7668  if (ldirect.eq.1) then
    77     write(unitheader) ibdate,ibtime, flexversion
     69    write(unitheader) ibdate,ibtime, trim(flexversion)
    7870  else
    79     write(unitheader) iedate,ietime, flexversion
     71    write(unitheader) iedate,ietime, trim(flexversion)
    8072  endif
    8173
  • tests/NILU/basic_tests

    rdd6a4aa rca350ba  
    11#WORKSPACE=/xnilu_wrk/flexbuild
    22#WORKSPACE=/home/ignacio/repos/
    3 FP_exec=$WORKSPACE/src/FLEXPART
     3FP_exec=$WORKSPACE/src/FP_ecmwf_gfortran
    44path_flextest=$WORKSPACE/flextest/
    55declare -a test_names=('1' 'HelloWorld' 'Fwd1' 'Fwd2' 'Bwd1' 'Volc' '2')
  • tests/NILU/run_tests

    rdd6a4aa rca350ba  
    99#FP_exec=/home/ignacio/repos/flexpart/src/FP_ecmwf_gfortran
    1010#FP_exec=/xnilu_wrk/flexbuild/tests/NILU/FP_ecmwf_gfortran
    11 #FP_exec=$WORKSPACE/src/FP_ecmwf_gfortran
    12 # CTBTO unified executable
    13 FP_exec=$WORKSPACE/src/FLEXPART
     11FP_exec=$WORKSPACE/src/FP_ecmwf_gfortran
    1412#path_flextest=/home/ignacio/repos/flextest/
    1513#path_flextest=/xnilu_wrk/flexbuild/flextest/
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG