source: flexpart.git/src/readcommand.f90 @ d7935de

univie
Last change on this file since d7935de was d7935de, checked in by pesei <petra seibert at univie ac at>, 6 years ago

modify most input read subroutines

changed some variable names (mostly for I-N reasons)
includes two names appearing also in timemanager, com_mod
corrected a few mistakes
simplified some parts of code
changed options/RELEASES which is in nml fmt correspondingly

  • Property mode set to 100644
File size: 24.9 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine readcommand
23
24  !*****************************************************************************
25  !                                                                            *
26  !     This routine reads the user specifications for the current model run.  *
27  !                                                                            *
28  !     Author: A. Stohl                                                       *
29  !                                                                            *
30  !     18 May 1996                                                            *
31  !     Unknown, unknown: various                                              *
32  !     HSO, 1 July 2014: Added optional namelist input                        *
33  !     Unknown, unknown: various                                              *
34  !     Petra Seibert, 2018-06-08: improve error msgs                          *
35  !     PS 6/2015: Minor changes in variable names and layout                  *
36  !                                                                            *
37  !*****************************************************************************
38  !                                                                            *
39  ! Variables:                                                                 *
40  ! bdate                beginning date as Julian date                         *
41  ! ctl                  factor by which time step must be smaller than        *
42  !                      Lagrangian time scale                                 *
43  ! ibdate,ibtime        beginnning date and time (YYYYMMDD, HHMISS)           *
44  ! ideltas [s]          modelling period                                      *
45  ! iedate,ietime        ending date and time (YYYYMMDD, HHMISS)               *
46  ! ifine                reduction factor for vertical wind time step          *
47  ! outputforeachrel     for forward runs it is possible either to create      *
48  !                      one outputfield or several for each releasepoint      *
49  ! iflux                switch to turn on (1)/off (0) flux calculations       *
50  ! iout                 1 for conc. (residence time for backward runs) output,*
51  !                      2 for mixing ratio output, 3 both, 4 for plume        *
52  !                      trajectory output, 5 = options 1 and 4                *
53  ! ipin                 1 continue simulation with dumped particle data, 0 no *
54  ! ipout                0 no particle dump, 1 every output time, 3 only at end*
55  ! itsplit [s]          time constant for particle splitting                  *
56  ! loutaver [s]         concentration output is an average over loutaver      *
57  !                      seconds                                               *
58  ! loutsample [s]       average is computed from samples taken every [s]      *
59  !                      seconds                                               *
60  ! loutstep [s]         time interval of concentration output                 *
61  ! lsynctime [s]        synchronisation time interval for all particles       *
62  ! lagespectra          switch to turn on (1)/off (0) calculation of age      *
63  !                      spectra                                               *
64  ! lconvection          value of either 0 and 1 indicating mixing by          *
65  !                      convection                                            *
66  !                      = 0 .. no convection                                  *
67  !                      + 1 .. parameterisation of mixing by subgrid-scale    *
68  !                              convection = on                               *
69  ! lsubgrid             switch to turn on (1)/off (0) subgrid topography      *
70  !                      parameterization                                      *
71  ! method               method used to compute the particle pseudovelocities  *
72  ! mdomainfill          1 use domain-filling option, 0 not, 2 use strat. O3   *
73  !                                                                            *
74  ! Constants:                                                                 *
75  ! unitcommand          unit connected to file COMMAND                        *
76  !                                                                            *
77  !*****************************************************************************
78
79  use par_mod
80  use com_mod
81
82  implicit none
83
84  real(kind=dp) :: juldate
85  character(len=50) :: line
86  logical :: old
87  integer :: ios, icmdstat
88
89  namelist /nml_command/ &
90    ldirect, &
91    ibdate,ibtime, &
92    iedate,ietime, &
93    loutstep, &
94    loutaver, &
95    loutsample, &
96    itsplit, &
97    lsynctime, &
98    ctl, &
99    ifine, &
100    iout, &
101    ipout, &
102    lsubgrid, &
103    lconvection, &
104    lagespectra, &
105    ipin, &
106    ioutputforeachrelease, &
107    iflux, &
108    mdomainfill, &
109    ind_source, &
110    ind_receptor, &
111    mquasilag, &
112    nested_output, &
113    linit_cond, &
114    lnetcdfout, &
115    surf_only, &
116    iflagcbl, &
117    path_ohfields
118
119! Set default values for namelist
120    ldirect=0
121    ibdate=20000101
122    ibtime=0
123    iedate=20000102
124    ietime=0
125    loutstep=10800
126    loutaver=10800
127    loutsample=900
128    itsplit=999999999
129    lsynctime=900
130    ctl=-5.0
131    ifine=4
132    iout=3
133    ipout=0
134    lsubgrid=1
135    lconvection=1
136    lagespectra=0
137    ipin=1
138    ioutputforeachrelease=1
139    iflux=1
140    mdomainfill=0
141    ind_source=1
142    ind_receptor=1
143    mquasilag=0
144    nested_output=0
145    linit_cond=0
146    lnetcdfout=0
147    surf_only=0
148    iflagcbl=0 ! if using old-style COMMAND file, set to 1 here to use mc cbl routine
149    path_ohfields="../../flexin/"
150
151  !Af set release-switch
152    wetbkdep=.false.
153    drybkdep=.false.
154 
155  ! Open the command file and read user options
156  ! Namelist input first: try to read as namelist file
157  !**************************************************************************
158  open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', &
159    form='formatted',err=999)
160
161! try namelist input
162  read(unitcommand, nml_command, iostat=ios)
163  close(unitcommand)
164
165  ! distinguish namelist from fixed text input
166
167  if (ios .ne. 0) then ! simple text file format
168 
169    open(unitcommand,file=path(1)(1:length(1))//'COMMAND',status='old', err=999)
170
171    ! Check the format of the COMMAND file
172    ! (either in free format or using formatted mask)
173    ! Use of formatted mask is assumed if line 10 contains the word 'DIRECTION'
174    !**************************************************************************
175
176    call skplin(9,unitcommand)
177    read (unitcommand,900) line
178    if (index(line,'LDIRECT') .eq. 0) then
179      old = .false.
180      if (lroot) write(*,*) 'COMMAND in old short format, &
181           &please update to namelist format'
182    else
183      old = .true.
184      if (lroot) write(*,*) 'COMMAND in old long format, &
185           &please update to namelist format'
186    endif
187    rewind(unitcommand)
188
189
190    ! Read parameters
191    !****************
192
193    call skplin(7,unitcommand)
194    if (old) call skplin(1,unitcommand)
195    read(unitcommand,*) ldirect
196    if (old) call skplin(3,unitcommand)
197    read(unitcommand,*) ibdate,ibtime
198    if (old) call skplin(3,unitcommand)
199    read(unitcommand,*) iedate,ietime
200    if (old) call skplin(3,unitcommand)
201    read(unitcommand,*) loutstep
202    if (old) call skplin(3,unitcommand)
203    read(unitcommand,*) loutaver
204    if (old) call skplin(3,unitcommand)
205    read(unitcommand,*) loutsample
206    if (old) call skplin(3,unitcommand)
207    read(unitcommand,*) itsplit
208    if (old) call skplin(3,unitcommand)
209    read(unitcommand,*) lsynctime
210    if (old) call skplin(3,unitcommand)
211    read(unitcommand,*) ctl
212    if (old) call skplin(3,unitcommand)
213    read(unitcommand,*) ifine
214    if (old) call skplin(3,unitcommand)
215    read(unitcommand,*) iout
216    if (old) call skplin(3,unitcommand)
217    read(unitcommand,*) ipout
218    if (old) call skplin(3,unitcommand)
219    read(unitcommand,*) lsubgrid
220    if (old) call skplin(3,unitcommand)
221    read(unitcommand,*) lconvection
222    if (old) call skplin(3,unitcommand)
223    read(unitcommand,*) lagespectra
224    if (old) call skplin(3,unitcommand)
225    read(unitcommand,*) ipin
226    if (old) call skplin(3,unitcommand)
227    read(unitcommand,*) ioutputforeachrelease
228    if (old) call skplin(3,unitcommand)
229    read(unitcommand,*) iflux
230    if (old) call skplin(3,unitcommand)
231    read(unitcommand,*) mdomainfill
232    if (old) call skplin(3,unitcommand)
233    read(unitcommand,*) ind_source
234    if (old) call skplin(3,unitcommand)
235    read(unitcommand,*) ind_receptor
236    if (old) call skplin(3,unitcommand)
237    read(unitcommand,*) mquasilag
238    if (old) call skplin(3,unitcommand)
239    read(unitcommand,*) nested_output
240    if (old) call skplin(3,unitcommand)
241    read(unitcommand,*) linit_cond
242    if (old) call skplin(3,unitcommand)
243    read(unitcommand,*) surf_only
244    ! Removed for backwards compatibility.
245    ! if (old) call skplin(3,unitcommand)  !added by mc
246    ! read(unitcommand,*) iflagcbl          !added by mc
247
248    close(unitcommand)
249
250  endif ! input format
251
252  ! write command file in namelist format to output directory if requested
253  if (nmlout.and.lroot) then
254    open(unitcommand,file=path(2)(1:length(2))//'COMMAND.namelist',err=998)
255    write(unitcommand,nml=nml_command)
256    close(unitcommand)
257  endif
258
259  ifine=max(ifine,1)
260
261  ! Determine how Markov chain is formulated (for w or for w/sigw)
262  !***************************************************************
263  if (iflagcbl.eq.1) then !added by mc to set parameters for CBL simulations
264    turbswitch=.true.
265    if (lsynctime.gt.maxtl) lsynctime=maxtl  !maxtl defined in com_mod.f90
266    if (ctl.lt.5) then
267      print*,'WARNING: CBL flag active; ctl (TLu/dt) has been set to 5'
268      ctl=5.
269    endif
270    if (ifine*ctl.lt.50.) then
271      ifine=int(50./ctl)+1
272      print *,'WARNING: CBL flag active; ctl (TLW/dt) was < 50,'// &
273        ' ifine has been re-set to', ifine
274    endif
275    print*,'WARNING: CBL flag active; reduced ctl is ',ctl*ifine
276    print*,'WARNING: CBL flag active; lsynctime is ',lsynctime
277  else                    !added by mc
278  ! note PS: shouldn't we print some msg as above also in the ntext case?
279    if (ctl.ge.0.1) then
280      turbswitch=.true.
281    else
282      turbswitch=.false.
283      ifine=1
284    endif
285  endif                   !added by mc
286  fine=1./real(ifine)
287  ctl=1./ctl
288
289! Set the switches required for the various options for input/output units
290!*************************************************************************
291!AF Set the switches IND_REL and IND_SAMP for the release and sampling
292!Af switches for the releasefile:
293!Af IND_REL =  1 : xmass * rho
294!Af IND_REL =  0 : xmass * 1
295
296!Af switches for the conccalcfile:
297!AF IND_SAMP =  0 : xmass * 1
298!Af IND_SAMP = -1 : xmass / rho
299
300!AF IND_SOURCE switches between different units for concentrations at the source
301!Af   NOTE that in backward simulations the release of computational particles
302!Af   takes place at the "receptor" and the sampling of p[articles at the "source".
303!Af          1 = mass units
304!Af          2 = mass mixing ratio units
305!Af IND_RECEPTOR switches between different units for concentrations at the receptor
306!Af          1 = mass units
307!Af          2 = mass mixing ratio units
308!            3 = wet deposition in outputfield
309!            4 = dry deposition in outputfield
310
311  if ( ldirect .eq. 1 ) then  ! FWD-Run
312  !Af set release-switch
313     if (ind_source .eq. 1 ) then !mass
314        ind_rel = 0
315     else ! mass mix
316        ind_rel = 1
317     endif
318  !Af set sampling switch
319     if (ind_receptor .eq. 1) then !mass
320        ind_samp = 0
321     else ! mass mix
322        ind_samp = -1
323     endif
324  elseif (ldirect .eq. -1 ) then !BWD-Run
325  !Af set sampling switch
326     if (ind_source .eq. 1 ) then !mass
327        ind_samp = -1
328     else ! mass mix
329        ind_samp = 0
330     endif
331! note PS: why do we suddenly switch to CASE syntax??
332! not helpful.
333     select case (ind_receptor)
334     case (1)  !  1 .. concentration at receptor
335        ind_rel = 1
336     case (2)  !  2 .. mixing ratio at receptor
337        ind_rel = 0
338     case (3)  ! 3 .. wet deposition in outputfield
339        ind_rel = 3
340        if (lroot) then
341          write(*,*) ' #### FLEXPART WET DEPOSITION BACKWARD MODE    #### '
342          write(*,*) ' #### Release height is forced to 0 - 20 km    #### '
343          write(*,*) ' #### Release is performed above ground lev    #### '
344        end if
345         wetbkdep=.true.
346         allocate(xscav_frac1(maxpart,maxspec))
347     case (4)  ! 4 .. dry deposition in outputfield
348         ind_rel = 4
349         if (lroot) then
350           write(*,*) ' #### FLEXPART DRY DEPOSITION BACKWARD MODE    #### '
351           write(*,*) ' #### Releaseheight is forced to 0 - 2*href    #### '
352           write(*,*) ' #### Release is performed above ground lev    #### '
353         end if
354         drybkdep=.true.
355         allocate(xscav_frac1(maxpart,maxspec))
356     end select
357  endif
358
359  !*************************************************************
360  ! Check whether valid options have been chosen in file COMMAND
361  !*************************************************************
362
363  ! Check options for initial condition output: Switch off for forward runs
364  !************************************************************************
365
366  if (ldirect.eq.1) linit_cond=0
367  if ((linit_cond.lt.0).or.(linit_cond.gt.2)) then
368    write(*,*) ' #### FLEXPART MODEL ERROR! INVALID OPTION    #### '
369    write(*,*) ' #### FOR LINIT_COND IN FILE "COMMAND".       #### '
370    stop
371  endif
372
373  ! Check input dates
374  !******************
375
376  if (iedate.lt.ibdate) then
377    write(*,*) ' #### FLEXPART MODEL ERROR! BEGINNING DATE    #### '
378    write(*,*) ' #### IS LARGER THAN ENDING DATE. CHANGE      #### '
379    write(*,*) ' #### EITHER POINT 2 OR POINT 3 IN FILE       #### '
380    write(*,*) ' #### "COMMAND".                              #### '
381    stop
382  else if (iedate.eq.ibdate) then
383    if (ietime.lt.ibtime) then
384    write(*,*) ' #### FLEXPART MODEL ERROR! BEGINNING TIME    #### '
385    write(*,*) ' #### IS LARGER THAN ENDING TIME. CHANGE      #### '
386    write(*,*) ' #### EITHER POINT 2 OR POINT 3 IN FILE       #### '
387    write(*,*) ' #### "COMMAND".                              #### '
388    stop
389    endif
390  endif
391
392
393  ! Determine kind of dispersion method
394  !************************************
395
396  if (ctl.gt.0.) then
397    method=1
398    mintime=minstep
399  else
400    method=0
401    mintime=lsynctime
402  endif
403
404!  check for netcdf output switch (use for non-namelist input only!)
405  if (iout.ge.8) then
406     lnetcdfout = 1
407     iout = iout - 8
408#ifndef USE_NCF
409     write(*,*) 'ERROR: netcdf output not activated during compile '// &
410       'time but used in COMMAND file!'
411     write(*,*) 'Please recompile with netcdf library (`make [...] ncf=yes`)'//&
412       ' or use standard output format.'
413     stop
414#endif
415  endif
416
417  ! Check whether a valid option for gridded model output has been chosen
418  !**********************************************************************
419
420  if (iout.lt.1 .or. iout.gt.6) then
421    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
422    write(*,*) ' #### IOUT MUST BE 1, 2, 3, 4 OR 5 FOR        #### '
423    write(*,*) ' #### STANDARD FLEXPART OUTPUT OR  9 - 13     #### '
424    write(*,*) ' #### FOR NETCDF OUTPUT                       #### '
425    stop
426  endif
427
428  !AF check consistency between units and volume mixing ratio
429  if ( (iout.eq.2       .or. iout.eq.3) .and. &
430       (ind_source.gt.1 .or. ind_receptor.gt.1) ) then
431    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
432    write(*,*) ' #### VOLUME MIXING RATIO ONLY SUPPORTED      #### '
433    write(*,*) ' #### FOR MASS UNITS (at the moment)          #### '
434    stop
435  endif
436
437
438  ! For quasilag output for each release is forbidden
439  !*****************************************************************************
440
441  if ((ioutputforeachrelease.eq.1).and.(mquasilag.eq.1)) then
442      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
443      write(*,*) '#### OUTPUTFOREACHRELEASE AND QUASILAGRANGIAN####'
444      write(*,*) '#### MODE IS NOT POSSIBLE   !                ####'
445      stop
446  endif
447
448
449  ! For quasilag backward is forbidden
450  !*****************************************************************************
451
452  if ((ldirect.lt.0).and.(mquasilag.eq.1)) then
453      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
454      write(*,*) '#### FOR BACKWARD RUNS, QUASILAGRANGIAN MODE ####'
455      write(*,*) '#### IS NOT POSSIBLE   !                     ####'
456      stop
457  endif
458
459
460  ! For backward runs one releasefield for all releases makes no sense,
461  ! For quasilag and domainfill ioutputforechrelease is forbidden
462  !*****************************************************************************
463
464  if ((ldirect.lt.0).and.(ioutputforeachrelease.eq.0)) then
465      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
466      write(*,*) '#### FOR BACKWARD RUNS, IOUTPUTFOREACHRLEASE ####'
467      write(*,*) '#### MUST BE SET TO ONE!                     ####'
468      stop
469  endif
470
471
472  ! For backward runs one releasefield for all releases makes no sense,
473  ! and is "forbidden"
474  !*****************************************************************************
475
476  if ((mdomainfill.eq.1).and.(ioutputforeachrelease.eq.1)) then
477      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
478      write(*,*) '#### FOR DOMAIN FILLING RUNS OUTPUT FOR      ####'
479      write(*,*) '#### EACH RELEASE IS FORBIDDEN !             ####'
480      stop
481  endif
482
483
484  ! For domain-filling trajectories, a plume centroid trajectory makes no sense,
485  ! For backward runs, only residence time output (iout=1) or plume trajectories
486  ! (iout=4), or both (iout=5) makes sense; other output options are "forbidden"
487  !*****************************************************************************
488
489  if (ldirect.lt.0) then
490    if ((iout.eq.2).or.(iout.eq.3)) then
491      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
492      write(*,*) '#### FOR BACKWARD RUNS, IOUT MUST BE 1,4,OR 5####'
493      stop
494    endif
495  endif
496
497
498  ! For domain-filling trajectories, a plume centroid trajectory makes no sense,
499  ! and is "forbidden"
500  !*****************************************************************************
501
502  if (mdomainfill.ge.1) then
503    if ((iout.eq.4).or.(iout.eq.5)) then
504      write(*,*) '#### FLEXPART MODEL ERROR! FILE COMMAND:     ####'
505      write(*,*) '#### FOR DOMAIN-FILLING TRAJECTORY OPTION,   ####'
506      write(*,*) '#### IOUT MUST NOT BE SET TO 4 OR 5.         ####'
507      stop
508    endif
509  endif
510
511
512
513  ! Check whether a valid options for particle dump has been chosen
514  !****************************************************************
515
516  if ((ipout.ne.0).and.(ipout.ne.1).and.(ipout.ne.2)) then
517    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
518    write(*,*) ' #### IPOUT MUST BE 1, 2 OR 3!                #### '
519    stop
520  endif
521
522  if(lsubgrid.ne.1.and.verbosity.eq.0) then
523    write(*,*) '             ----------------               '
524    write(*,*) ' INFORMATION: SUBGRIDSCALE TERRAIN EFFECT IS'
525    write(*,*) ' NOT PARAMETERIZED DURING THIS SIMULATION.  '
526    write(*,*) '             ----------------               '
527  endif
528
529
530  ! Check whether convection scheme is either turned on or off
531  !***********************************************************
532
533  if ((lconvection.ne.0).and.(lconvection.ne.1)) then
534    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
535    write(*,*) ' #### LCONVECTION MUST BE SET TO EITHER 1 OR 0#### '
536    stop
537  endif
538
539
540  ! Check whether synchronisation interval is sufficiently short
541  !*************************************************************
542
543  if (lsynctime.gt.(idiffnorm/2)) then
544    write(*,*) ' #### FLEXPART MODEL ERROR! SYNCHRONISATION   #### '
545    write(*,*) ' #### TIME IS TOO LONG. MAKE IT SHORTER.      #### '
546    write(*,*) ' #### MINIMUM HAS TO BE: ', idiffnorm/2
547    stop
548  endif
549
550
551  ! Check consistency of the intervals, sampling periods, etc., for model output
552  !*****************************************************************************
553
554  if (loutaver.eq.0) then
555    write(*,*) ' #### FLEXPART MODEL ERROR! TIME AVERAGE OF   #### '
556    write(*,*) ' #### CONCENTRATION FIELD OUTPUT MUST NOT BE  #### '
557    write(*,*) ' #### ZERO.                                   #### '
558    write(*,*) ' #### CHANGE INPUT IN FILE COMMAND.           #### '
559    stop
560  endif
561
562  if (loutaver.gt.loutstep) then
563    write(*,*) ' #### FLEXPART MODEL ERROR! TIME AVERAGE OF   #### '
564    write(*,*) ' #### CONCENTRATION FIELD OUTPUT MUST NOT BE  #### '
565    write(*,*) ' #### GREATER THAN INTERVAL OF OUTPUT.        #### '
566    write(*,*) ' #### CHANGE INPUT IN FILE COMMAND.           #### '
567    stop
568  endif
569
570  if (loutsample.gt.loutaver) then
571    write(*,*) ' #### FLEXPART MODEL ERROR! SAMPLING TIME OF  #### '
572    write(*,*) ' #### CONCENTRATION FIELD OUTPUT MUST NOT BE  #### '
573    write(*,*) ' #### GREATER THAN TIME AVERAGE OF OUTPUT.    #### '
574    write(*,*) ' #### CHANGE INPUT IN FILE COMMAND.           #### '
575    stop
576  endif
577
578  if (mod(loutaver,lsynctime).ne.0) then
579    write(*,*) ' #### FLEXPART MODEL ERROR! AVERAGING TIME OF #### '
580    write(*,*) ' #### CONCENTRATION FIELD MUST BE A MULTIPLE  #### '
581    write(*,*) ' #### OF THE SYNCHRONISATION INTERVAL         #### '
582    stop
583  endif
584
585  if ((loutaver/lsynctime).lt.2) then
586    write(*,*) ' #### FLEXPART MODEL ERROR! AVERAGING TIME OF #### '
587    write(*,*) ' #### CONCENTRATION FIELD MUST BE AT LEAST    #### '
588    write(*,*) ' #### TWICE THE SYNCHRONISATION INTERVAL      #### '
589    stop
590  endif
591
592  if (mod(loutstep,lsynctime).ne.0) then
593    write(*,*) ' #### FLEXPART MODEL ERROR! INTERVAL BETWEEN  #### '
594    write(*,*) ' #### CONCENTRATION FIELDS MUST BE A MULTIPLE #### '
595    write(*,*) ' #### OF THE SYNCHRONISATION INTERVAL         #### '
596    stop
597  endif
598
599  if ((loutstep/lsynctime).lt.2) then
600    write(*,*) ' #### FLEXPART MODEL ERROR! INTERVAL BETWEEN  #### '
601    write(*,*) ' #### CONCENTRATION FIELDS MUST BE AT LEAST   #### '
602    write(*,*) ' #### TWICE THE SYNCHRONISATION INTERVAL      #### '
603    stop
604  endif
605
606  if (mod(loutsample,lsynctime).ne.0) then
607    write(*,*) ' #### FLEXPART MODEL ERROR! SAMPLING TIME OF  #### '
608    write(*,*) ' #### CONCENTRATION FIELD MUST BE A MULTIPLE  #### '
609    write(*,*) ' #### OF THE SYNCHRONISATION INTERVAL         #### '
610    stop
611  endif
612
613  if (itsplit.lt.loutaver) then
614    write(*,*) ' #### FLEXPART MODEL ERROR! SPLITTING TIME FOR#### '
615    write(*,*) ' #### PARTICLES IS TOO SHORT. PLEASE INCREASE #### '
616    write(*,*) ' #### SPLITTING TIME CONSTANT.                #### '
617    stop
618  endif
619
620  if ((mquasilag.eq.1).and.(iout.ge.4)) then
621    write(*,*) ' #### FLEXPART MODEL ERROR! CONFLICTING       #### '
622    write(*,*) ' #### OPTIONS: IF MQUASILAG=1, PLUME          #### '
623    write(*,*) ' #### TRAJECTORY OUTPUT IS IMPOSSIBLE.        #### '
624    stop
625  endif
626
627  ! Compute modeling time in seconds and beginning date in Julian date
628  !*******************************************************************
629
630  outstep=real(abs(loutstep))
631  if (ldirect.eq.1) then
632    bdate=juldate(ibdate,ibtime)
633    edate=juldate(iedate,ietime)
634    ideltas=nint((edate-bdate)*86400.)
635  else if (ldirect.eq.-1) then
636    loutaver=-1*loutaver
637    loutstep=-1*loutstep
638    loutsample=-1*loutsample
639    lsynctime=-1*lsynctime
640    bdate=juldate(iedate,ietime)
641    edate=juldate(ibdate,ibtime)
642    ideltas=nint((edate-bdate)*86400.)
643  else
644    write(*,*) ' #### FLEXPART MODEL ERROR! DIRECTION IN'
645    write(*,*) ' #### FILE "COMMAND" MUST BE EITHER -1 OR 1.'
646    stop
647  endif
648
649  return
650
651998 write(*,900) ' #### FLEXPART MODEL ERROR! FILE "COMMAND.namelist"'
652  write(*,900)   ' #### CANNOT WRITE TO '// &
653    path(2)(1:length(2))//'COMMAND.namelist'
654  stop 'stopped in readcommand'
655
656999 write(*,900) ' #### FLEXPART MODEL ERROR! FILE "COMMAND"'
657  write(*,900)   ' #### CANNOT OPEN '//path(1)(1:length(1))//'COMMAND'
658  stop 'stopped in readcommand'
659
660900 format(a)
661
662end subroutine readcommand
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG