MFIX  2016-1
main.f
Go to the documentation of this file.
1 ! -*- f90 -*-
2 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
3 ! !
4 ! MODULE: MAIN !
5 ! !
6 ! Purpose: Main module for top level mfix subroutines. !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9 
10  MODULE main
11 
12  use exit, only: mfix_exit
13 
14 !-----------------------------------------------
15 ! Module variables
16 !-----------------------------------------------
17 ! Final value of CPU time.
18  DOUBLE PRECISION :: cpu1
19 ! time used for computations.
20  DOUBLE PRECISION :: cputime_used, walltime_used
21 ! DISTIO variable for specifying the mfix version
22  CHARACTER(LEN=512) :: version
23 ! environment variable
24 !$ CHARACTER(LEN=512) :: omp_num_threads
25 !$ INTEGER :: length
26 !$ INTEGER :: status
27 
28 ! Number of iterations
29  INTEGER :: nit_total
30 ! used for activating check_data_30
31  INTEGER :: ncheck, dncheck
32 
33 ! Flag to save results and cleanly exit.
34  LOGICAL :: exit_signal = .false.
35 
36  CHARACTER(LEN=80), DIMENSION(100) :: cmd_line_args
37  INTEGER :: cmd_line_args_count = 0
38 
39  CONTAINS
40 
41  SUBROUTINE initialize
42 
43 #ifdef MPI
44  USE mpi, only: mpi_comm_world, mpi_barrier ! ignore-depcomp
45 #endif
46  USE cdist, only: bdoing_postmfix
48  USE check, only: check_mass_balance
50  USE coeff, only: init_coeff
51  USE compar, only: mpierr, mype, pe_io
52  USE cont, only: do_cont
54  USE discretelement, only: discrete_element
55  USE drag, only: f_gs
58  USE fldvar, only: rop_g, rop_s
59  USE funits, only: dmp_log, unit_log, unit_res
60  USE machine, only: start_log, end_log
62  USE mfix_netcdf, only: mfix_usingnetcdf
63  USE output, only: dbgprn_layout
66  USE param1, only: n_spx, undefined, zero
67  USE pgcor, only: d_e, d_n, d_t, phase_4_p_g, switch_4_p_g
68  USE physprop, only: mmax
70  USE qmom_kinetic_equation, only: qmomk
71  USE read_input, only: get_data
72  USE run, only: id_version, ier
75  USE time_cpu, only: cpu00, wall0
77  USE vtk, only: write_vtk_files
78 
79  IMPLICIT NONE
80 
81 !$ INTEGER num_threads, threads_specified, omp_id
82 !$ INTEGER omp_get_num_threads
83 !$ INTEGER omp_get_thread_num
84 
85  ! Temporary storage for DT
86  DOUBLE PRECISION :: DT_tmp
87  ! Save TIME in input file for RESTART_2
88  DOUBLE PRECISION :: TIME_SAVE
89 
90  INTEGER :: LL, MM
91 
92 ! DISTIO
93 ! If you change the value below in this subroutine, you must also
94 ! change it in write_res0.f and the value should also be consistent
95 ! with the check in read_res0
96  version = 'RES = 01.6'
97 
98  bdoing_postmfix = .false.
99 
100 ! Invoke MPI initialization routines and get rank info.
101  CALL parallel_init
102  CALL gen_log_basename
103 
104 ! we want only PE_IO to write out common error messages
105  dmp_log = (mype == pe_io)
106 
107 ! set the version.release of the software
108  id_version = '2016-1'
109 
110 ! set automatic restart flag to false
111 ! AUTOMATIC_RESTART = .FALSE.
112 ! ITER_RESTART = 1
113 
114 ! specify the number of processors to be used
115 !$ call get_environment_variable("OMP_NUM_THREADS",omp_num_threads,length,status, .true.)
116 !$ if (status.eq.0 .and. length.ne.0) then
117 !$ read(omp_num_threads,*) threads_specified
118 !$ else
119 !$ WRITE(*,'(A,$)') 'Enter the number of threads to be used for SMP: '
120 !$ READ(*,*) threads_specified
121 !$ endif
122 
123 !$ call omp_set_num_threads(threads_specified)
124 
125 ! Find the number of processors used
126 !$omp parallel
127 !$ num_threads = omp_get_num_threads()
128 !$ omp_id = omp_get_thread_num()
129 !$ if(omp_id.eq.0) Write(*,*)' Number of threads used for SMP = ', num_threads
130 !$omp end parallel
131 
132 ! Set machine dependent constants
133  CALL machine_cons
134 
135 ! Get the date and time. They give the unique run_id in binary output
136 ! files
137  CALL get_run_id
138 
139 ! AEOLUS: stop trigger mechanism to terminate MFIX normally before batch
140 ! queue terminates. timestep at the beginning of execution
141  CALL cpu_time (cpu00)
142  wall0 = wall_time()
143 
144 ! Read input data, check data, do computations for IC and BC locations
145 ! and flows, and set geometry parameters such as X, X_E, DToDX, etc.
146  CALL get_data
147 
148 ! Write the initial part of the standard output file
149  CALL write_out0
150  IF(.NOT.cartesian_grid) CALL write_flags
151 
152 ! Write the initial part of the special output file(s)
153  CALL write_usr0
154 
155 !$ CALL START_LOG
156 !$ IF(DMP_LOG)WRITE (UNIT_LOG, *) ' '
157 !$ IF(DMP_LOG)WRITE (UNIT_LOG, *) ' Number of processors used = ', threads_specified
158 !$ IF(DMP_LOG)WRITE (UNIT_LOG, *) ' '
159 !$ CALL END_LOG
160 
161 ! setup for PC quickwin application
162  CALL pc_quickwin
163 
164  CALL init_err_msg('MFIX')
165 
166 
167 ! if not netcdf writes asked for ... globally turn off netcdf
168  if(mfix_usingnetcdf()) then
169  bglobalnetcdf = .false.
170  do ll = 1,20
171  if (bwrite_netcdf(ll)) bglobalnetcdf = .true.
172  enddo
173  endif
174 
175  dt_tmp = dt
176  SELECT CASE (trim(run_type))
177 
178  CASE ('NEW')
179 ! Write the initial part of the restart files
180  CALL write_res0
181  DO ll = 1, n_spx
182  CALL write_spx0 (ll, 0)
183  ENDDO
184 
185  CASE ('RESTART_1')
186 ! Read the time-dependent part of the restart file
187  CALL read_res1
188  WRITE(err_msg, 1010) time, nstep
189  CALL flush_err_msg()
190 
191  CASE ('RESTART_2')
192  time_save = time
193 ! DISTIO
194  if (mype .ne. pe_io .and. bdist_io .and. bstart_with_one_res) then
195  write (unit_res,rec=1) version
196  write (unit_res,rec=2) 4
197  write (unit_res,rec=3) 4
198  endif
199 
200  CALL read_res1
201  time = time_save
202 
203 1010 FORMAT('Message 1010: Read in data from .RES file for TIME = ',&
204  g12.5,/'Time step number (NSTEP) =',i7)
205 
206  WRITE(err_msg, 1010) time, nstep
207  CALL flush_err_msg()
208 
209  CALL write_res0
210 
211 ! Writing the RES1 and SPX1 can only be done here when re-indexing is turned off
212 ! This will be done after the cell re-indexing is done later in this file.
213 ! This allows restarting independently of the re-indexing setting between
214 ! the previous and current run.
215  IF(.NOT.re_indexing) THEN
216  CALL write_res1
217  DO ll = 1, n_spx
218  CALL write_spx0 (ll, 0)
219  CALL write_spx1 (ll, 0)
220  END DO
221  call write_netcdf(0,0,time)
222  ENDIF
223 
224  CASE DEFAULT
225  CALL start_log
226  IF(dmp_log)WRITE (unit_log, *) &
227  ' MFIX: Do not know how to process'
228  IF(dmp_log)WRITE (unit_log, *) ' RUN_TYPE in data file'
229  CALL end_log
230  call mfix_exit(mype)
231 
232  END SELECT
233 
234 #ifdef MPI
235  call mpi_barrier(mpi_comm_world,mpierr)
236 #endif
237 
238  IF (dt_tmp /= undefined) THEN
239  dt = max(dt_min,min(dt_max,dt))
240  ELSE
241  dt = dt_tmp
242  ENDIF
243 
244 ! Set arrays for computing indices. A secondary call is made
245 ! after cut cell-preprocessing to update array indices.
246  IF(cartesian_grid) THEN
247  CALL set_increments
248  CALL set_increments3
249  ENDIF
250 
251 ! IF(.NOT.RE_INDEXING) CALL WRITE_IJK_VALUES
252 
253 ! Set the flags for wall surfaces impermeable and identify flow
254 ! boundaries using FLAG_E, FLAG_N, and FLAG_T
255  CALL set_flags1
256 
257 ! Update flags for Cartesian_GRID.
259 
260 ! Calculate cell volumes and face areas
261  IF(.NOT.cartesian_grid) CALL set_geometry1
262 
263 ! Find corner cells and set their face areas to zero
264  IF(.NOT.cartesian_grid) THEN
265  CALL get_corner_cells()
266  ELSE
268  ENDIF
269 
270 ! Set constant physical properties
271  CALL set_constprop
272 
273 ! Set initial conditions
274  CALL set_ic
275 
276 ! Set point sources.
277  CALL set_ps
278 
279 ! Set boundary conditions
280  CALL zero_norm_vel
281  CALL set_bc0
282 
283 ! Cartesian grid implementation
284  IF(cartesian_grid) CALL cg_set_bc0
285 
286 ! Set gas mixture molecular weight
287  CALL set_mw_mix_g
288 
289 ! Set the pressure field for a fluidized bed
290  IF (run_type == 'NEW') CALL set_fluidbed_p
291 
292 ! Initialize densities.
293  IF (run_type == 'NEW') CALL set_ro_g
294  IF (run_type == 'NEW') CALL set_ro_s
295 
296 ! Initialize time dependent boundary conditions
297  CALL set_bc1
298 
299 ! Check the field variable data and report errors.
300  IF(.NOT.cartesian_grid) CALL check_data_20
301 
302 !=======================================================================
303 ! JFD: START MODIFICATION FOR RE-INDEXING CELLS
304 !=======================================================================
305  IF(cartesian_grid.AND.re_indexing) THEN
306 
307  IF(mype == pe_io) THEN
308  WRITE(*,"(72('='))")
309  WRITE(*,*)' RE-INDEXING CELLS FOR CARTESIAN GRID...'
310  ENDIF
311  CALL re_index_arrays
312 
313 
314  !IF(myPE == PE_IO)print*,'Calling REPORT_BEST_IJK_SIZE:'
315  !CALL REPORT_BEST_IJK_SIZE
317  !IF(myPE == PE_IO)print*,'Exiting MFIX after REPORT_BEST_IJK_SIZE.'
318 
319  IF(mype == pe_io) WRITE(*,"(72('='))")
320 
321 ! In case of a RESTART_2, write the RES1 and SPX1 files here
322 ! This was commented out earlier in this file.
323  IF(run_type == 'RESTART_2') THEN
324  CALL write_res1
325  DO ll = 1, n_spx
326  CALL write_spx0 (ll, 0)
327  CALL write_spx1 (ll, 0)
328  END DO
329  call write_netcdf(0,0,time)
330  ENDIF
331  ENDIF
332 !=======================================================================
333 ! JFD: END MODIFICATION FOR RE-INDEXING CELLS
334 !=======================================================================
335 
336 ! Setup VTK data for regular (no cut cells) grid
338 
339  IF(discrete_element) CALL make_arrays_des
340  IF(qmomk) CALL qmomk_make_arrays
341 
342 ! Set the inflow/outflow BCs for DEM solids
343  IF(dem_solids) CALL set_bc_dem
344 ! Set the inflow/outflow BC for PIC solids
345  IF(pic_solids) CALL set_bc_pic
346 
347 ! Set the inital properties of each particle.
348  IF(dem_solids) CALL set_ic_dem
349 
350 ! AEOLUS: debug prints
351  if (dbgprn_layout .or. bdist_io) then
352  !write (*,*) myPE , ' E.4 ... version = ' , version(1:33)
353  call debug_write_layout()
354  call write_parallel_info()
355  endif
356 
357 ! Initializations for CPU time calculations in iterate
358  cpuos = 0.
359  CALL cpu_time (cpu1)
360  cpu_nlog = cpu1
361  time_nlog = time - dt
362 
363 ! Get the initial value of CPU time
364  CALL cpu_time (cpu0)
365 
366 ! Find the solution of the equations from TIME to TSTOP at
367 ! intervals of DT
368 
369 !-----------------------------------------------
370 
371  ncheck = nstep
372  dncheck = 1
373  cpu_io = zero
374  nit_total = 0
375 
376  CALL init_output_vars
377 
378 ! Parse residual strings
379  CALL parse_resid_string ()
380 
381 ! Call user-defined subroutine to set constants, check data, etc.
382  IF (call_usr) CALL usr0
383 
384  CALL rrates_init()
385 
386 ! Calculate all the coefficients once before entering the time loop
387  CALL init_coeff(ier)
388 
389  DO mm=1, mmax
390  f_gs(1,mm) = zero
391  ENDDO
392 
393 ! Remove undefined values at wall cells for scalars
394  CALL undef_2_0 (rop_g)
395  DO mm = 1, mmax
396  CALL undef_2_0 (rop_s(1,mm))
397  ENDDO
398 
399 ! Initialize d's and e's to zero
400  DO mm = 0, mmax
401  d_e(1,mm) = zero
402  d_n(1,mm) = zero
403  d_t(1,mm) = zero
404  ENDDO
405  e_e(:) = zero
406  e_n(:) = zero
407  e_t(:) = zero
408 
409 ! calculate shear velocities if periodic shear BCs are used
410  IF(shear) CALL cal_d(v_sh)
411 
412 ! Initialize check_mass_balance. This routine is not active by default.
413 ! Specify a reporting interval (hard-wired in the routine) to activate
414 ! the routine.
415  Call check_mass_balance (0)
416 
417 ! sof modification: now it's only needed to do this once before time-loop
418 ! Mark the phase whose continuity will be solved and used to correct
419 ! void/volume fraction in calc_vol_fr (see subroutine for details)
422 
423  END SUBROUTINE initialize
424 
425  SUBROUTINE finalize
427  USE cutcell, only: cartesian_grid
428  USE dashboard
430  USE error_manager, only: finl_err_msg
431  USE machine, only: wall_time
432  USE parallel_mpi, only: parallel_fin
433  USE run, only: dt, call_usr, dt_min, get_tunit, tunit
434  USE time_cpu
435  IMPLICIT NONE
436 
437 ! Call user-defined subroutine after time-loop.
438  IF (call_usr) CALL usr3
439 
440 ! Get the final value of CPU time. The difference gives the
441 ! CPU time used for the computations.
442  CALL cpu_time (cpu1)
443 
444 ! Compute the CPU time and write it out in the .OUT file.
448 
449 ! JFD: cartesian grid implementation
450  IF(write_dashboard) THEN
451  IF(dt>=dt_min) THEN
452  run_status = 'Complete.'
453  ELSE
454  run_status = 'DT < DT_MIN. Recovery not possible!'
455  ENDIF
458  ENDIF
460 
461 ! Finalize and terminate MPI
462  call parallel_fin
463 
464  CALL finl_err_msg
465 
466  END SUBROUTINE finalize
467 
468 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
469 ! !
470 ! Subroutine: GEN_LOG_BASENAME !
471 ! Author: Aytekin Gel Date: 19-SEP-03 !
472 ! !
473 ! Purpose: Generate the file base for DMP logs. !
474 ! !
475 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
476  SUBROUTINE gen_log_basename
478  use compar, only: mype
479  use compar, only: fbname
480 
481  implicit none
482 
483 ! Variables for generating file basename with processor id
484  INTEGER :: i1, i10, i100, i1000, i10000
485 
486 ! PAR_I/O Generate file basename for LOG files
487  i10000 = int(mype/10000)
488  i1000 = int((mype-i10000*10000)/1000)
489  i100 = int((mype-i10000*10000-i1000*1000)/100)
490  i10 = int((mype-i10000*10000-i1000*1000-i100*100)/10)
491  i1 = int((mype-i10000*10000-i1000*1000-i100*100-i10*10)/1)
492 
493  i10000 = i10000 + 48
494  i1000 = i1000 + 48
495  i100 = i100 + 48
496  i10 = i10 + 48
497  i1 = i1 + 48
498 
499  fbname=char(i10000)//char(i1000)//char(i100)//char(i10)//char(i1)
500 
501  RETURN
502  END SUBROUTINE gen_log_basename
503 
504 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
505 ! C
506 ! Module name: debug_write() C
507 ! Purpose: Write out full geometry index setup information for the
508 ! case
509 ! C
510 ! Author: Aytekin Gel Date: 19-SEP-03 C
511 ! Reviewer: Date: C
512 ! C
513 ! C
514 ! Literature/Document References: C
515 ! C
516 ! Variables referenced: C
517 ! Variables modified: C
518 ! C
519 ! Local variables: C
520 ! C
521 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
522 
523  SUBROUTINE debug_write_layout()
525 !-----------------------------------------------
526 ! Modules
527 !-----------------------------------------------
528  USE cdist
529  USE compar
530  USE functions
531  USE funits
532  USE geometry
533  USE indices
534  USE leqsol
535  USE mpi_utility
536  USE parallel
537  USE param
538  USE param1
539  USE run
540  USE sendrecv
541  USE sendrecv3
542  USE time_cpu
543  IMPLICIT NONE
544 !-----------------------------------------------
545 ! Local Variables
546 !-----------------------------------------------
547 ! phase index
548  INTEGER :: M
549 ! indices
550  INTEGER :: i, j, k, ijk, ijk_GL, ijk_PROC, ijk_IO
551 !
552  integer :: indxA, indxA_gl, indxB, indxB_gl, indxC, indxC_gl
553  integer :: indxD, indxD_gl, indxE, indxE_gl, indxF, indxF_gl
554  integer :: indxG, indxG_gl, indxH, indxH_gl
555 !
556  logical :: amgdbg = .true.
557 
558  character(LEN=80) :: fname
559 
560 !DISTIO
561 ! fname = "layout_xxxx.txt"
562 ! write (fname(8:11),'(i4.4)') myPE
563  fname = "layout_xxxxx.txt"
564  write (fname(8:12),'(i5.5)') mype
565  open (unit=11,file=fname,status='unknown')
566 
567  write (11,*) ' ********************************************'
568  write (11,*) ' ********************************************'
569  write (11,*) ' ********************************************'
570  write (11,*) ' ********************************************'
571  write (11,*) ' '
572  write (11,*) ' '
573  write (11,*) ' myPE = ' , mype
574  write (11,*) ' '
575  write (11,*) ' '
576 
577 
578  IF (amgdbg .OR. bdist_io) THEN
579  write(11,.AND..AND."('BLK1: Running from istart3,iend3 jstart3, jend3 kstart3, kend3')")
580  write(11,"(' ( i , j, k) => ijk ijk_GL ijk_PROC ijk_IO')")
581  write(11,"(' ==================== ===== ======= ======== ======')")
582  DO k = kstart3, kend3
583  DO i = istart3,iend3
584  DO j = jstart3, jend3
585  ijk = funijk(i,j,k)
586  ijk_gl = funijk_gl(i,j,k)
587  ijk_proc = funijk_proc(i,j,k,mype)
588  ijk_io = funijk_io(i,j,k)
589  write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',4(I8,' , '))") &
590  i,j,k,ijk,ijk_gl,ijk_proc,ijk_io
591  ENDDO
592  ENDDO
593  ENDDO
594 
595  write(11,"(/,/,'BLK2: Print out Bottom, South, West, East, North, Top neighbors')")
596  write(11,"(' ( i , j, k) => ijk ijk_GL B_of S_of W_of E_of N_of T_of')")
597  write(11,"(' ==================== ===== ======= ====== ====== ====== ====== ====== ======')")
598  DO k = kstart3, kend3
599  DO i = istart3,iend3
600  DO j = jstart3, jend3
601  ijk = funijk(i,j,k)
602  ijk_gl = funijk_gl(i,j,k)
603  write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',2(I7,' , '),6(I7,2X))") &
604  i,j,k,ijk,ijk_gl,bottom_of(ijk),south_of(ijk),west_of(ijk),&
605  east_of(ijk),north_of(ijk),top_of(ijk)
606  ENDDO
607  ENDDO
608  ENDDO
609 
610  write(11,"(/,/,'BLK3: Print out km, jm, im, ip, jp, kp neighbors')")
611  write(11,"(' ( i , j, k) => ijk ijk_GL km_of jm_of im_of ip_of jp_of kp_of')")
612  write(11,"(' ==================== ===== ======= ====== ====== ====== ====== ====== ======')")
613  DO k = kstart3, kend3
614  DO i = istart3,iend3
615  DO j = jstart3, jend3
616  ijk = funijk(i,j,k)
617  ijk_gl = funijk_gl(i,j,k)
618  write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',2(I7,' , '),6(I7,2X))") &
619  i,j,k,ijk,ijk_gl,km_of(ijk),jm_of(ijk),im_of(ijk),&
620  ip_of(ijk),jp_of(ijk),kp_of(ijk)
621  ENDDO
622  ENDDO
623  ENDDO
624 
625  write(11,"(/,'BLK4a: Active Fluid Cells:FLUID_AT(ijk)=.T.',/,&
626  & ' ( i , j, k) => ijk [ x , , z]')")
627  write(11,"(' ==================== ===== ====================')")
628  DO ijk = ijkstart3, ijkend3
629  i = i_of(ijk)
630  j = j_of(ijk)
631  k = k_of(ijk)
632 
633  ! IF (FLOW_AT_E(IJK)) THEN
634  IF (fluid_at(ijk)) THEN
635  ! write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',I8)") I,J,K,ijk
636  write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',I8,' [',E12.5,',',E12.5,' ]')") i,j,k,ijk,x(i),z(k)
637  ENDIF
638  ENDDO
639 
640  write(11,.NOT."(/,'BLK4b: Cells that are (WALL_AT(IJK)) = .T.',/,&
641  & ' ( i , j, k) => ijk [ x , , z]')")
642  write(11,"(' ==================== ===== ====================')")
643  DO ijk = ijkstart3, ijkend3
644  i = i_of(ijk)
645  j = j_of(ijk)
646  k = k_of(ijk)
647 
648  IF (.NOT.wall_at(ijk)) THEN
649  ! write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',I8)") I,J,K,ijk
650  write(11,"(' (',I4,' , ',I4,' , ',I4,') => ',I8,' [',E12.5,',',E12.5,' ]')") i,j,k,ijk,x(i),z(k)
651  ENDIF
652  ENDDO
653 
654  DO k = kstart3, kend3
655  DO i = istart3,iend3
656  DO j = jstart3, jend3
657  ijk = funijk(i,j,k)
658  ijk_gl = funijk_gl(i,j,k)
659 
660  if (i == istart2 .AND. j == jstart2) then
661  indxa = ijk
662  indxa_gl = ijk_gl
663  endif
664  if (i == istart1 .AND. j == jstart1) then
665  indxe = ijk
666  indxe_gl = ijk_gl
667  endif
668  if (i == istart2 .AND. j == jend2) then
669  indxb = ijk
670  indxb_gl = ijk_gl
671  endif
672  if (i == istart1 .AND. j == jend1) then
673  indxf = ijk
674  indxf_gl = ijk_gl
675  endif
676  if (i == iend1 .AND. j == jstart1) then
677  indxh = ijk
678  indxh_gl = ijk_gl
679  endif
680  if (i == iend2 .AND. j == jstart2) then
681  indxd = ijk
682  indxd_gl = ijk_gl
683  endif
684  if (i == iend1 .AND. j == jend1) then
685  indxg = ijk
686  indxg_gl = ijk_gl
687  endif
688  if (i == iend2 .AND. j == jend2) then
689  indxc = ijk
690  indxc_gl = ijk_gl
691  endif
692  ENDDO
693  ENDDO
694  write(11,"('BLK5:')")
695  write(11,"(57('='))")
696  write(11,"('k= ',I5,/,57('='))") k
697  write(11,"('B= ',I5,' (',I7,')',20X,'C= ',I5,' (',I7,')',/)") indxb, indxb_gl, &
698  indxc, indxc_gl
699  ! write(UNIT_LOG,"(' \',34X,'/')")
700  ! write(UNIT_LOG,"(2X,'\',32X,'/')")
701  write(11,"(3X,'F= ',I5,' (',I7,')',12X,'G= ',I5,' (',I7,')')") indxf, indxf_gl, &
702  indxg, indxg_gl
703  write(11,"(4(9X,'|',29X,'|',/))")
704  write(11,"(3X,'E= ',I5,' (',I7,')',12X,'H= ',I5,' (',I7,')',/)") indxe, indxe_gl, &
705  indxh, indxh_gl
706  ! write(UNIT_LOG,"(2X,'/',32X,'\')")
707  ! write(UNIT_LOG,"('/',34X,'\')")
708  write(11,"('A= ',I5,' (',I7,')',20X,'D= ',I5,' (',I7,')',/,/)") indxa, indxa_gl, &
709  indxd, indxd_gl
710 
711  ! write(UNIT_LOG,"(' (',I4,' , ',I4,' , ',I4,') => ',2(I7,' , '),6(I7,2X))") &
712  ! i,j,k,ijk,ijk_GL,bottom_of(ijk),south_of(ijk),west_of(ijk),&
713  ! east_of(ijk),north_of(ijk),top_of(ijk)
714 
715  ENDDO
716 
717  ! write(UNIT_LOG,"(/,' ( i , j, k) => ijk (Active Fluid)')")
718  ! write(UNIT_LOG,"(' ==================== =====')")
719  ! DO ijk = ijkstart3, ijkend3
720  ! I = I_OF(IJK)
721  ! J = J_OF(IJK)
722  ! K = K_OF(IJK)
723 
724  ! IF (FLOW_AT_E(IJK)) THEN
725  ! IF (FLUID_AT(IJK)) THEN
726  ! write(UNIT_LOG,"(' (',I4,' , ',I4,' , ',I4,') => ',I8)") I,J,K,ijk
727  ! ENDIF
728  ! END DO
729 
730 
731  endif ! end if(amgdbg .or. bdist_io)
732 
733  m = 0
734  ! CALL WRITE_AB_M (A_M, B_M, IJKMAX2, M, IER)
735 
736  IF (amgdbg .OR. bdist_io) THEN
737  write(11,"(/,/,'BLK6: ========= ORIGINAL MFIX VARIABLES ===========')")
738  write(11,"('PE ',I5,': imin1 = ',I6,3X,'imax1= ',I6,/,'PE ',I5,': jmin1 = ',I6,3X,'jmax1= ',I6)") &
740  write(11,"('PE ',I5,': kmin1 = ',I6,3X,'kmax1= ',I6)") mype,kmin1,kmax1
741  write(11,"('-----')")
742  write(11,"('PE ',I5,': imin2 = ',I6,3X,'imax2= ',I6,/,'PE ',I5,': jmin2 = ',I6,3X,'jmax2= ',I6)") &
744  write(11,"('PE ',I5,': kmin2 = ',I6,3X,'kmax2= ',I6)") mype,kmin2,kmax2
745  write(11,"('----- Below xxx3 set is DMP extension ------------')")
746  write(11,"('PE ',I5,': imin3 = ',I6,3X,'imax3= ',I6,/,'PE ',I5,': jmin3 = ',I6,3X,'jmax3= ',I6)") &
748  write(11,"('PE ',I5,': kmin3 = ',I6,3X,'kmax3= ',I6)") mype,kmin3,kmax3
749  write(11,"('----- End of Below xxx3 set is DMP extension -----')")
750  ! write(11,"('PE ',I5,': ijkmax2= ',I6)") myPE,ijkmax2
751  write(11,"('PE ',I5,': ijmax2 = ',I6)") mype,ijmax2
752  write(11,"('PE ',I5,': ijkmin1= ',I6,' ijkmax1= ',I12)") mype,ijkmin1, ijkmax1
753  write(11,"('PE ',I5,': ',6X,' ijkmax2= ',I12)") mype,ijkmax2
754  write(11,"('PE ',I5,': ',6X,' ijkmax3= ',I12)") mype,ijkmax3
755  write(11,"('PE ',I5,': ijkmin4= ',I6,' ijkmax4= ',I12)") mype,ijkmin4, ijkmax4
756 
757 
758  write(11,"(/,/,' ========= DMP EXTENSION VARIABLES ===========')")
759  ! write(UNIT_LOG,"('PE ',I5,': ijksize = ',I6)") myPE,ijksize
760  write(11,"('PE ',I5,': ijksize3 = ',I6,3X,'ijksize3_all = ',I6)") mype,ijksize3,ijksize3_all(mype)
761  write(11,"('PE ',I5,': ijksize4 = ',I6,3X,'ijksize4_all = ',I6)") mype,ijksize4,ijksize4_all(mype)
762  write(11,"('PE ',I5,': ijkstart3 = ',I6,3X,'ijkend3 = ',I6)") mype,ijkstart3, ijkend3
763  write(11,"('PE ',I5,': ijkstart3_all = ',I6,3X,'ijkstart4_all = ',I6)") mype,ijkstart3_all(mype),ijkstart4_all(mype)
764  write(11,"('PE ',I5,': istart_all = ',I6,3X,'iend_all = ',I6,/,'PE ',I5,': jstart_all = ',I6,3X,'jend_all = ',I6)") &
766  write(11,"('PE ',I5,': kstart_all = ',I6,3X,'kend_all = ',I6,/,'----------------------')") &
768 
769  write(11,"('PE ',I5,': istart1_all= ',I6,3X,'iend1_all= ',I6,/,'PE ',I5,': jstart1_all= ',I6,3X,'jend3_all= ',I6)") &
771  write(11,"('PE ',I5,': kstart1_all= ',I6,3X,'kend1_all= ',I6,/,'----------------------')") &
773 
774  write(11,"('PE ',I5,': istart2_all= ',I6,3X,'iend2_all= ',I6,/,'PE ',I5,': jstart2_all= ',I6,3X,'jend3_all= ',I6)") &
776  write(11,"('PE ',I5,': kstart2_all= ',I6,3X,'kend2_all= ',I6,/,'----------------------')") &
778 
779  write(11,"('PE ',I5,': istart3_all= ',I6,3X,'iend3_all= ',I6,/,'PE ',I5,': jstart3_all= ',I6,3X,'jend3_all= ',I6)") &
781  write(11,"('PE ',I5,': kstart3_all= ',I6,3X,'kend3_all= ',I6,/,'----------------------')") &
783 
784  write(11,"('PE ',I5,': istart1= ',I6,3X,'iend1= ',I6,/,'PE ',I5,': jstart1= ',I6,3X,'jend1= ',I6)") &
786  write(11,"('PE ',I5,': kstart1= ',I6,3X,'kend1= ',I6,/,'----------------------')") &
788  write(11,"('PE ',I5,': istart2= ',I6,3X,'iend2= ',I6,/,'PE ',I5,': jstart2= ',I6,3X,'jend2= ',I6)") &
790  write(11,"('PE ',I5,': kstart2= ',I6,3X,'kend2= ',I6,/,'----------------------')") &
792  write(11,"('PE ',I5,': istart3= ',I6,3X,'iend3= ',I6,/,'PE ',I5,': jstart3= ',I6,3X,'jend3= ',I6)") &
794  write(11,"('PE ',I5,': kstart3= ',I6,3X,'kend3= ',I6,/,'----------------------')") &
796 
797  ENDIF ! end if(amgdbg .or. bdist_io)
798 
799  close(unit=11)
800 
801 
802  RETURN
803  END SUBROUTINE debug_write_layout
804 
805 
806 
807  !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
808 
809  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
810 
811  SUBROUTINE write_parallel_info()
813  !-----------------------------------------------
814  ! M o d u l e s
815  !-----------------------------------------------
816  USE compar
817  USE functions
818  USE funits
819  USE geometry
820  USE indices
821  USE leqsol
822  USE mpi_utility
823  USE parallel
824  USE param
825  USE param1
826  USE run
827  USE sendrecv
828  USE sendrecv3
829  USE time_cpu
830  IMPLICIT NONE
831  !-----------------------------------------------
832  ! Dummy arguments
833  !-----------------------------------------------
834  ! Local Variables
835  !-----------------------------------------------
836  ! phase index
837  INTEGER :: M
838  ! indices
839  INTEGER :: i, j, k, ijk, ijk_GL, ijk_PROC, ijk_IO
840  !
841  character(LEN=80) :: fname
842  !-----------------------------------------------
843 
844  !DISTIO
845  ! fname = "p_info_xxxx.txt"
846  ! write (fname(8:11),'(i4.4)') myPE
847  fname = "p_info_xxxxx.txt"
848  write (fname(8:12),'(i5.5)') mype
849  open (unit=11,file=fname,status='unknown')
850 
851  write (11,*) mype , ' = myPE'
852 
853  write (11,*) mype , istart3,iend3
854  write (11,*) mype , jstart3,jend3
855  write (11,*) mype , kstart3,kend3
856 
857  write(11,.AND..AND."('BLK1: Running from istart3,iend3 jstart3, jend3 kstart3, kend3')")
858  write(11,"(' ( i , j, k) ijk ijk_GL ijk_PROC ijk_IO')")
859  write(11,"(' ==================== ===== ======= ======== ======')")
860  DO k = kstart3, kend3
861  DO i = istart3,iend3
862  DO j = jstart3, jend3
863  ijk = funijk(i,j,k)
864  ijk_gl = funijk_gl(i,j,k)
865  ijk_proc = funijk_proc(i,j,k,mype)
866  ijk_io = funijk_io(i,j,k)
867  write(11,"(' ',I4,' ',I4,' ',I4,' ',4(I8,' '))" ) &
868  i,j,k,ijk,ijk_gl,ijk_proc,ijk_io
869  ENDDO
870  ENDDO
871  ENDDO
872 
873  m = 0
874  ! CALL WRITE_AB_M (A_M, B_M, IJKMAX2, M, IER)
875 
876  close(unit=11)
877 
878  RETURN
879  END SUBROUTINE write_parallel_info
880 
881  !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
882  ! !
883  ! SUBROUTINE: DO_MPI_BCAST !
884  ! !
885  ! Purpose: Used by pymfix for broadcasting commands. !
886  ! !
887  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
888  function do_mpi_bcast(str)
889 #ifdef MPI
890  use mpi ! ignore-depcomp
891 #endif
892  implicit none
893 
894  ! TODO: return a dynamically allocated string, instead of fixed size of 100,000 bytes
895  character(len=100000),intent(in) :: str
896  character :: aa(100000)
897  character :: do_mpi_bcast(100000)
898  integer :: ii
899  integer :: ierr
900 
901  do ii = 1,len(str)
902  aa(ii) = str(ii:ii)
903  end do
904 
905 #ifdef MPI
906  call mpi_bcast(aa,100000,mpi_character,0,mpi_comm_world,ierr)
907 #endif
908 
909  do ii = 1,100000
910  do_mpi_bcast(ii:ii) = aa(ii)
911  end do
912 
913  end function do_mpi_bcast
914 
916  implicit none
918  end subroutine do_write_dbg_vtu_and_vtp_files
919 
920  subroutine do_backupres
922  implicit none
923  call backup_res
924  end subroutine do_backupres
925 
926  subroutine do_reinit(filename)
927  use reinit, only: reinitialize
928  implicit none
929  ! filename of uploaded mfix.dat file
930  character(len=*), intent(in) :: filename
931  call reinitialize(filename)
932  end subroutine do_reinit
933 
934  subroutine do_abort
935  use compar, only: mype
936  implicit none
937  call mfix_exit(mype)
938  end subroutine do_abort
939 
940  !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
941  ! Subroutine: ADD_COMMAND_LINE_ARGUMENT !
942  ! Author: M.Meredith Date: 03-FEB-16 !
943  ! !
944  ! Purpose: Save command line arguments in CMD_LINE_ARGS array. !
945  ! Used by both mfix.f and pymfix. !
946  ! !
947  !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
948  SUBROUTINE add_command_line_argument(ARG)
949  implicit none
950  CHARACTER(LEN=80), INTENT(IN) :: ARG
951 
953 
954  if (cmd_line_args_count > 100) THEN
955  print *,"TOO MANY COMMAND LINE ARGUMENTS"
956  stop
957  ENDIF
958 
960 
961  END SUBROUTINE add_command_line_argument
962 
963 END MODULE main
integer, dimension(:), allocatable istart1_all
Definition: compar_mod.f:65
integer jend2
Definition: compar_mod.f:80
subroutine write_spx0(L, UNIT_ADD)
Definition: write_spx0.f:10
subroutine set_flags1
Definition: set_flags.f:364
subroutine write_res0
Definition: write_res0.f:23
logical write_dashboard
Definition: dashboard_mod.f:3
integer iend3
Definition: compar_mod.f:80
integer, dimension(:), allocatable kstart1_all
Definition: compar_mod.f:65
subroutine mark_phase_4_cor(PHASE_4_P_G, PHASE_4_P_S, DO_CONT, MCP, DO_P_S, SWITCH_4_P_G, SWITCH_4_P_S)
subroutine parallel_init()
logical re_indexing
Definition: cutcell_mod.f:16
logical dbgprn_layout
Definition: output_mod.f:35
double precision time_nlog
Definition: time_cpu_mod.f:6
logical dem_solids
Definition: run_mod.f:257
logical dmp_log
Definition: funits_mod.f:6
subroutine init_output_vars
integer imax2
Definition: geometry_mod.f:61
integer, dimension(:), allocatable i_of
Definition: indices_mod.f:45
character(len=5) fbname
Definition: compar_mod.f:100
subroutine report_best_processor_size
double precision, dimension(:), allocatable e_n
Definition: pscor_mod.f:17
integer jstart3
Definition: compar_mod.f:80
subroutine setup_vtk_no_cutcell
Definition: vtk_out.f:1887
integer ijkend3
Definition: compar_mod.f:80
integer kend1
Definition: compar_mod.f:80
logical bdoing_postmfix
Definition: cdist_mod.f:6
double precision cpu_io
Definition: time_cpu_mod.f:10
integer istart1
Definition: compar_mod.f:80
integer ijkmin4
Definition: geometry_mod.f:96
subroutine set_ic
Definition: set_ic.f:11
logical bdist_io
Definition: cdist_mod.f:4
subroutine finl_err_msg
subroutine update_dashboard(NIT, TLEFT, TUNIT)
subroutine output_manager(EXIT_SIGNAL, FINISHED)
integer, dimension(:), allocatable kend1_all
Definition: compar_mod.f:65
subroutine get_corner_cells()
Definition: corner.f:21
integer iend1
Definition: compar_mod.f:80
integer, dimension(:), allocatable istart2_all
Definition: compar_mod.f:65
double precision, dimension(:,:), allocatable d_n
Definition: pgcor_mod.f:14
logical shear
Definition: run_mod.f:175
Definition: pgcor_mod.f:1
integer imax3
Definition: geometry_mod.f:91
subroutine set_increments3
subroutine write_spx1(L, unit_add)
Definition: write_spx1.f:26
integer ijkmax2
Definition: geometry_mod.f:80
subroutine set_ps
Definition: set_ps.f:12
subroutine check_mass_balance(init)
Definition: check_mod.f:38
logical write_vtk_files
Definition: vtk_mod.f:24
integer ijksize3
Definition: compar_mod.f:80
double precision function wall_time()
Definition: machine_mod.f:135
integer, dimension(:), allocatable kstart2_all
Definition: compar_mod.f:65
subroutine check_data_20
Definition: check_data_20.f:27
integer istart2
Definition: compar_mod.f:80
double precision cpu_nlog
Definition: time_cpu_mod.f:6
subroutine set_geometry1
Definition: set_geometry1.f:19
integer dncheck
Definition: main.f:31
integer, dimension(:), allocatable iend3_all
Definition: compar_mod.f:65
integer ijkmax1
Definition: geometry_mod.f:86
integer iend2
Definition: compar_mod.f:80
subroutine write_netcdf(L, unit_add, the_time)
Definition: write_spx1.f:839
character(len=512) version
Definition: main.f:22
Definition: drag_mod.f:11
double precision, dimension(:,:), allocatable d_e
Definition: pgcor_mod.f:12
subroutine initialize
Definition: main.f:42
subroutine set_ro_g
Definition: set_ro_g.f:24
integer kstart3
Definition: compar_mod.f:80
integer, dimension(:), allocatable ijksize4_all
Definition: compar_mod.f:90
subroutine set_increments
double precision dt
Definition: run_mod.f:51
subroutine set_ro_s
Definition: set_ro_s.f:12
double precision, dimension(:), allocatable e_t
Definition: pscor_mod.f:19
logical automatic_restart
Definition: run_mod.f:36
integer, dimension(:), allocatable istart_all
Definition: compar_mod.f:65
Definition: vtk_mod.f:1
subroutine do_reinit(filename)
Definition: main.f:927
subroutine rrates_init()
Definition: rrates_init.f:17
integer, parameter n_spx
Definition: param1_mod.f:5
subroutine read_res1
Definition: read_res1.f:26
double precision, parameter undefined
Definition: param1_mod.f:18
subroutine zero_norm_vel
Definition: zero_norm_vel.f:18
integer mpierr
Definition: compar_mod.f:27
double precision, dimension(:,:), allocatable d_t
Definition: pgcor_mod.f:16
subroutine usr3
Definition: usr3.f:28
integer kend2
Definition: compar_mod.f:80
double precision cpuos
Definition: time_cpu_mod.f:4
integer jmin2
Definition: geometry_mod.f:89
integer imin3
Definition: geometry_mod.f:90
integer ijksize4
Definition: compar_mod.f:94
integer kstart2
Definition: compar_mod.f:80
logical, dimension(:), allocatable do_cont
integer kstart1
Definition: compar_mod.f:80
integer kend3
Definition: compar_mod.f:80
integer ijkmin1
Definition: geometry_mod.f:84
logical bstart_with_one_res
Definition: cdist_mod.f:5
integer, dimension(:), allocatable phase_4_p_s
Definition: pscor_mod.f:28
integer ijkmax3
Definition: geometry_mod.f:82
subroutine qmomk_make_arrays
subroutine init_err_msg(CALLER)
integer, dimension(:), allocatable k_of
Definition: indices_mod.f:47
integer pe_io
Definition: compar_mod.f:30
integer ier
Definition: run_mod.f:265
double precision dt_max
Definition: run_mod.f:220
subroutine set_constprop
Definition: set_constprop.f:15
double precision cpu1
Definition: main.f:18
integer, dimension(:), allocatable ijkstart4_all
Definition: compar_mod.f:90
double precision cputime_used
Definition: main.f:20
integer kmax1
Definition: geometry_mod.f:58
integer, dimension(:), allocatable jend_all
Definition: compar_mod.f:65
integer, dimension(:), allocatable kstart3_all
Definition: compar_mod.f:65
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
integer, dimension(:), allocatable istart3_all
Definition: compar_mod.f:65
integer ijkmax4
Definition: geometry_mod.f:96
integer mmax
Definition: physprop_mod.f:19
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
subroutine write_res1
Definition: write_res1.f:26
integer, dimension(:), allocatable jend2_all
Definition: compar_mod.f:65
integer imax1
Definition: geometry_mod.f:54
integer jend3
Definition: compar_mod.f:80
integer jmax2
Definition: geometry_mod.f:63
logical, dimension(20) bwrite_netcdf
Definition: cdist_mod.f:10
character(len=40) run_status
Definition: dashboard_mod.f:8
Definition: exit.f:2
Definition: cdist_mod.f:2
subroutine add_command_line_argument(ARG)
Definition: main.f:949
integer jstart2
Definition: compar_mod.f:80
integer, dimension(:), allocatable iend2_all
Definition: compar_mod.f:65
integer, dimension(:), allocatable jstart3_all
Definition: compar_mod.f:65
subroutine init_coeff(IER)
Definition: coeff_mod.f:41
subroutine gen_log_basename
Definition: main.f:477
character(len=16) run_type
Definition: run_mod.f:33
integer, dimension(:), allocatable jstart_all
Definition: compar_mod.f:65
integer jmax3
Definition: geometry_mod.f:91
subroutine set_ic_dem
Definition: set_ic_dem.f:14
character function, dimension(100000) do_mpi_bcast(str)
Definition: main.f:889
double precision cpu00
Definition: time_cpu_mod.f:13
subroutine set_bc1
Definition: set_bc1.f:10
integer, dimension(:), allocatable kend2_all
Definition: compar_mod.f:65
subroutine get_data
Definition: get_data.f:15
subroutine finalize
Definition: main.f:426
integer cmd_line_args_count
Definition: main.f:37
integer kmax2
Definition: geometry_mod.f:65
logical switch_4_p_g
Definition: pgcor_mod.f:26
character(len=4) tunit
Definition: run_mod.f:268
Definition: pscor_mod.f:1
integer jmax1
Definition: geometry_mod.f:56
subroutine set_fluidbed_p
integer, parameter unit_log
Definition: funits_mod.f:21
Definition: run_mod.f:13
subroutine parallel_fin()
subroutine set_bc0
Definition: set_bc0.f:13
double precision cpu0
Definition: time_cpu_mod.f:8
Definition: param_mod.f:2
subroutine machine_cons
Definition: machine_mod.f:54
integer mcp
Definition: pscor_mod.f:38
subroutine do_backupres
Definition: main.f:921
integer jmin3
Definition: geometry_mod.f:90
logical cartesian_grid
Definition: cutcell_mod.f:13
integer, dimension(:), allocatable jstart1_all
Definition: compar_mod.f:65
integer ijmax2
Definition: geometry_mod.f:78
integer jmin1
Definition: geometry_mod.f:42
integer, dimension(:), allocatable phase_4_p_g
Definition: pgcor_mod.f:22
subroutine reinitialize(filename)
Definition: reinitialize.f:13
integer kmax3
Definition: geometry_mod.f:91
subroutine write_dbg_vtu_and_vtp_files
Definition: vtk_out.f:16
integer, dimension(:), allocatable kend3_all
Definition: compar_mod.f:65
integer mype
Definition: compar_mod.f:24
integer nstep
Definition: run_mod.f:60
integer ijkstart3
Definition: compar_mod.f:80
integer, dimension(:), allocatable jend3_all
Definition: compar_mod.f:65
subroutine backup_res
subroutine set_bc_pic
Definition: set_bc_pic.f:14
logical function mfix_usingnetcdf()
subroutine debug_write_layout()
Definition: main.f:524
integer, dimension(:), allocatable jend1_all
Definition: compar_mod.f:65
integer kmin3
Definition: geometry_mod.f:90
subroutine usr0
Definition: usr0.f:29
character(len=line_length), dimension(line_count) err_msg
subroutine start_log
Definition: machine_mod.f:182
subroutine cal_d(V_sh)
Definition: cal_d.f:7
logical do_p_s
Definition: pscor_mod.f:35
subroutine parse_resid_string()
double precision, dimension(:,:), allocatable f_gs
Definition: drag_mod.f:14
character(len=80), dimension(100) cmd_line_args
Definition: main.f:36
integer, dimension(:), allocatable iend_all
Definition: compar_mod.f:65
integer, parameter unit_res
Definition: funits_mod.f:27
logical set_corner_cells
Definition: cutcell_mod.f:417
subroutine write_usr0
Definition: write_usr0.f:24
integer imin2
Definition: geometry_mod.f:89
subroutine re_index_arrays
subroutine undef_2_0(VARDUM)
Definition: undef_2_0.f:11
double precision dt_min
Definition: run_mod.f:223
subroutine check_bc_flags
double precision wall0
Definition: time_cpu_mod.f:14
subroutine cg_set_bc0
Definition: CG_set_bc0.f:25
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
Definition: main.f:10
Definition: coeff_mod.f:9
subroutine write_flags
Definition: write_out0.f:978
logical exit_signal
Definition: main.f:34
subroutine do_abort
Definition: main.f:935
double precision, dimension(:), allocatable z
Definition: geometry_mod.f:131
subroutine get_run_id
Definition: machine_mod.f:89
double precision, dimension(:), allocatable e_e
Definition: pscor_mod.f:15
subroutine write_out0
Definition: write_out0.f:10
logical bglobalnetcdf
Definition: cdist_mod.f:14
integer, dimension(:), allocatable kstart_all
Definition: compar_mod.f:65
subroutine do_write_dbg_vtu_and_vtp_files
Definition: main.f:916
integer imin1
Definition: geometry_mod.f:40
subroutine set_mw_mix_g
Definition: set_mw_mix_g.f:18
double precision time
Definition: run_mod.f:45
integer nit_total
Definition: main.f:29
subroutine pc_quickwin
Definition: machine_mod.f:219
subroutine write_parallel_info()
Definition: main.f:812
integer istart3
Definition: compar_mod.f:80
integer ncheck
Definition: main.f:31
integer, dimension(:), allocatable ijksize3_all
Definition: compar_mod.f:65
integer, dimension(:), allocatable jstart2_all
Definition: compar_mod.f:65
logical pic_solids
Definition: run_mod.f:258
subroutine set_bc_dem
Definition: set_bc_dem.f:13
integer, dimension(:), allocatable ijkstart3_all
Definition: compar_mod.f:65
integer, dimension(:), allocatable kend_all
Definition: compar_mod.f:65
integer kmin1
Definition: geometry_mod.f:44
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
subroutine get_tunit(TLEFT, TUNIT)
Definition: run_mod.f:277
integer, dimension(:), allocatable iend1_all
Definition: compar_mod.f:65
integer iter_restart
Definition: run_mod.f:39
double precision, dimension(:), allocatable x
Definition: geometry_mod.f:129
subroutine write_out3(CPU, WALL, IO)
Definition: write_out3.f:10
double precision, parameter zero
Definition: param1_mod.f:27
double precision walltime_used
Definition: main.f:20
logical switch_4_p_s
Definition: pscor_mod.f:32
subroutine end_log
Definition: machine_mod.f:208
character(len=10) id_version
Definition: run_mod.f:42
subroutine make_arrays_des
integer jend1
Definition: compar_mod.f:80
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
integer jstart1
Definition: compar_mod.f:80
double precision v_sh
Definition: run_mod.f:177
integer kmin2
Definition: geometry_mod.f:89
logical call_usr
Definition: run_mod.f:121