SPEED
WRITE_OUTPUT.f90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine write_output (nmonitlst, mpi_id, elem_mlst, local_el_num, ne_loc, cs_loc, cs_nnz_loc, sdeg_mat, nmat, u2, u1, u0, v1, nnod_loc, stress, strain, omega, xr_mlst, yr_mlst, zr_mlst, tt1, dt, dt2, option_out_var, count_mon, monitor_file, dbg, mu, gamma, b_instabilitycontrol, instability_maxval, b_instability_abort)
 Writes output results.
 

Function/Subroutine Documentation

◆ write_output()

subroutine write_output ( integer*4  nmonitlst,
integer*4  mpi_id,
integer*4, dimension(nmonitlst)  elem_mlst,
integer*4, dimension(ne_loc)  local_el_num,
integer*4  ne_loc,
integer*4, dimension(0:cs_nnz_loc)  cs_loc,
integer*4  cs_nnz_loc,
integer*4, dimension(nmat)  sdeg_mat,
integer*4  nmat,
real*8, dimension(3*nnod_loc)  u2,
real*8, dimension(3*nnod_loc)  u1,
real*8, dimension(3*nnod_loc)  u0,
real*8, dimension(3*nnod_loc)  v1,
integer*4  nnod_loc,
real*8, dimension(6*nnod_loc)  stress,
real*8, dimension(6*nnod_loc)  strain,
real*8, dimension(3*nnod_loc)  omega,
real*8, dimension(nmonitlst)  xr_mlst,
real*8, dimension(nmonitlst)  yr_mlst,
real*8, dimension(nmonitlst)  zr_mlst,
real*8  tt1,
real*8  dt,
real*8  dt2,
integer*4, dimension(6)  option_out_var,
integer*4  count_mon,
character*70  monitor_file,
integer*4  dbg,
real*8, dimension(nnod_loc)  mu,
real*8, dimension(nnod_loc)  gamma,
logical, intent(in)  b_instabilitycontrol,
real*8, intent(in)  instability_maxval,
logical, intent(out)  b_instability_abort 
)

Writes output results.

Author
Ilario Mazzieri
Date
September, 2013
Version
1.0
Parameters
[in]nmonitlstnmber of monitors
[in]mpi_idid mpi process
[in]elem_mlstlist of elements for monitors
[in]ne_locnumber of local elements
[in]local_el_numlocal element numeration
[in]cs_nnz_loclength of cs_loc
[in]cs_loclocal connectivity vector
[in]nmatnumber of materials
[in]sdeg_matpolynomial degree vector
[in]nnod_locnumber of local nodes
[in]u2displacement variables time t+1
[in]u1displacement variables time t
[in]u0displacement variables time t-1
[in]v1velocity variables time t
[in]stressstress tensor
[in]strainstrain tensor
[in]omegarotational tensor
[in]xr_mlstmonitors x-coordinate
[in]yr_mlstmonitors y-coordinate
[in]zr_mlstmonitors coordinate
[in]tt1current time
[in]dttime step
[in]dt2dt^2
[in]option_out_varoption for output
[in]count_monnumber of current monitors
[in]monitor_filedirectory where saving files
[in]dbgflag for debugging mode
[in]musecond elastic coefficient to print
[in]gammadamping coefficient to print
[in]b_instabilitycontrolflag to check numerical instability
[in]instability_maxvalcheck numerical instability
[out]b_instability_abortif true, simulation is unstable
[out]---Files MONITORXXXXXX.D (disp),MONITORXXXXXX.V (vel),MONITORXXXXXX.A (acc)

Definition at line 59 of file WRITE_OUTPUT.f90.

67
68
69 implicit none
70
71 character*70 :: monitor_file
72 character*70 :: monitor_file1,monitor_file2,monitor_file3,monitor_file4,monitor_file5,monitor_file6
73 character*70 :: monitor_file7,monitor_file8
74 character*14 :: file_monitor1,file_monitor2,file_monitor3,file_monitor4,file_monitor5,file_monitor6
75 character*14 :: file_monitor7,file_monitor8
76
77 integer*4 :: unit_monitor1,unit_monitor2,unit_monitor3,unit_monitor4,unit_monitor5,unit_monitor6
78 integer*4 :: unit_monitor7,unit_monitor8
79 integer*4 :: imon,ielem,ie,im,nn,k,j,i,is,in,iaz,count_mon,ishift,jshift,kshift,dbg
80 integer*4 :: nmonitlst, mpi_id, ne_loc, nmat, nnod_loc, cs_nnz_loc
81 integer*4, dimension(0:cs_nnz_loc) :: cs_loc
82 integer*4, dimension(nmonitlst) :: elem_mlst
83 integer*4, dimension(nmat) :: sdeg_mat
84 integer*4, dimension(ne_loc) :: local_el_num
85 integer*4, dimension(6) :: option_out_var
86 integer*4 :: mpi_ierr
87
88 real*8 :: tt1, dt, dt2
89 real*8 :: uxm,uym,uzm
90 real*8 :: vxm,vym,vzm
91 real*8 :: axm,aym,azm
92 real*8 :: variable1m,variable2m,variable3m,variable4m,variable5m,variable6m
93
94 real*8, dimension(:), allocatable :: variables_1,variables_2,variables_3
95 real*8, dimension(:), allocatable :: variables_4,variables_5,variables_6
96 real*8, dimension(:), allocatable :: variables_7,variables_8
97
98 real*8, dimension(:), allocatable :: ct, ww
99 real*8, dimension(:,:), allocatable :: dd
100 real*8, dimension(:,:,:), allocatable :: ux_el, uy_el, uz_el
101 real*8, dimension(:,:,:), allocatable :: variable1_el,variable2_el,variable3_el
102 real*8, dimension(:,:,:), allocatable :: variable4_el,variable5_el,variable6_el
103
104 real*8, dimension(3*nnod_loc) :: u1, u0, u2, v1, omega
105 real*8, dimension(6*nnod_loc) :: stress, strain
106 real*8, dimension(nnod_loc) :: mu, gamma
107 real*8, dimension(nmonitlst) ::xr_mlst, yr_mlst, zr_mlst
108
109 ! Instability control
110 real*8, intent(in) :: instability_maxval
111 logical, intent(in) :: b_instabilitycontrol
112 logical, intent(out) :: b_instability_abort
113
114
115 unit_monitor1 = 10*(mpi_id+1) + 1
116 unit_monitor2 = 10*(mpi_id+1) + 2
117 unit_monitor3 = 10*(mpi_id+1) + 3
118 unit_monitor4 = 10*(mpi_id+1) + 4
119 unit_monitor5 = 10*(mpi_id+1) + 5
120 unit_monitor6 = 10*(mpi_id+1) + 6
121
122 if (dbg .eq. 1) then
123 unit_monitor7 = 100*(mpi_id+1) + 1
124 unit_monitor8 = 100*(mpi_id+1) + 2
125 endif
126
127 if (option_out_var(1) .eq. 1) file_monitor1 = 'MONITOR00000.D'
128 if (option_out_var(2) .eq. 1) file_monitor2 = 'MONITOR00000.V'
129 if (option_out_var(3) .eq. 1) file_monitor3 = 'MONITOR00000.A'
130 if (option_out_var(4) .eq. 1) file_monitor4 = 'MONITOR00000.S'
131 if (option_out_var(5) .eq. 1) file_monitor5 = 'MONITOR00000.E'
132 if (option_out_var(6) .eq. 1) file_monitor6 = 'MONITOR00000.O'
133 if (dbg .eq. 1) then
134 file_monitor7 = 'MONITOR00000.M'
135 file_monitor8 = 'MONITOR00000.G'
136 endif
137
138
139 if (mpi_id .lt. 10) then
140 write(file_monitor1(12:12),'(i1)') mpi_id;
141 write(file_monitor2(12:12),'(i1)') mpi_id;
142 write(file_monitor3(12:12),'(i1)') mpi_id;
143 write(file_monitor4(12:12),'(i1)') mpi_id;
144 write(file_monitor5(12:12),'(i1)') mpi_id;
145 write(file_monitor6(12:12),'(i1)') mpi_id;
146 write(file_monitor7(12:12),'(i1)') mpi_id;
147 write(file_monitor8(12:12),'(i1)') mpi_id;
148
149 else if (mpi_id .lt. 100) then
150 write(file_monitor1(11:12),'(i2)') mpi_id;
151 write(file_monitor2(11:12),'(i2)') mpi_id;
152 write(file_monitor3(11:12),'(i2)') mpi_id;
153 write(file_monitor4(11:12),'(i2)') mpi_id;
154 write(file_monitor5(11:12),'(i2)') mpi_id;
155 write(file_monitor6(11:12),'(i2)') mpi_id;
156 write(file_monitor7(11:12),'(i1)') mpi_id;
157 write(file_monitor8(11:12),'(i1)') mpi_id;
158
159 else if (mpi_id .lt. 1000) then
160 write(file_monitor1(10:12),'(i3)') mpi_id;
161 write(file_monitor2(10:12),'(i3)') mpi_id;
162 write(file_monitor3(10:12),'(i3)') mpi_id;
163 write(file_monitor4(10:12),'(i3)') mpi_id;
164 write(file_monitor5(10:12),'(i3)') mpi_id;
165 write(file_monitor6(10:12),'(i3)') mpi_id;
166 write(file_monitor7(10:12),'(i3)') mpi_id;
167 write(file_monitor8(10:12),'(i3)') mpi_id;
168
169 else if (mpi_id .lt. 10000) then
170 write(file_monitor1(9:12),'(i4)') mpi_id;
171 write(file_monitor2(9:12),'(i4)') mpi_id;
172 write(file_monitor3(9:12),'(i4)') mpi_id;
173 write(file_monitor4(9:12),'(i4)') mpi_id;
174 write(file_monitor5(9:12),'(i4)') mpi_id;
175 write(file_monitor6(9:12),'(i4)') mpi_id;
176 write(file_monitor7(9:12),'(i4)') mpi_id;
177 write(file_monitor8(9:12),'(i4)') mpi_id;
178
179 else
180 write(file_monitor1(8:12),'(i5)') mpi_id
181 write(file_monitor2(8:12),'(i5)') mpi_id
182 write(file_monitor3(8:12),'(i5)') mpi_id
183 write(file_monitor4(8:12),'(i5)') mpi_id
184 write(file_monitor5(8:12),'(i5)') mpi_id
185 write(file_monitor6(8:12),'(i5)') mpi_id
186 write(file_monitor7(8:12),'(i5)') mpi_id
187 write(file_monitor8(8:12),'(i5)') mpi_id
188
189 endif
190
191 if (option_out_var(1) .eq. 1) then
192 if(len_trim(monitor_file) .ne. 70) then
193 monitor_file1 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor1
194 else
195 monitor_file1 = file_monitor1
196 endif
197 allocate(variables_1(0:3*count_mon))
198 open(unit_monitor1,file=monitor_file1,position='APPEND')
199 variables_1(0) = tt1
200 endif
201 if (option_out_var(2) .eq. 1) then
202 if(len_trim(monitor_file) .ne. 70) then
203 monitor_file2 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor2
204 else
205 monitor_file2 = file_monitor2
206 endif
207 allocate(variables_2(0:3*count_mon))
208 open(unit_monitor2,file=monitor_file2,position='APPEND')
209 variables_2(0) = tt1
210 endif
211 if (option_out_var(3) .eq. 1) then
212 if(len_trim(monitor_file) .ne. 70) then
213 monitor_file3 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor3
214 else
215 monitor_file3 = file_monitor3
216 endif
217 allocate(variables_3(0:3*count_mon))
218 open(unit_monitor3,file=monitor_file3,position='APPEND')
219 variables_3(0) = tt1
220 endif
221 if (option_out_var(4) .eq. 1) then
222 if(len_trim(monitor_file) .ne. 70) then
223 monitor_file4 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor4
224 else
225 monitor_file4 = file_monitor4
226 endif
227 allocate(variables_4(0:6*count_mon))
228 open(unit_monitor4,file=monitor_file4,position='APPEND')
229 variables_4(0) = tt1
230 endif
231 if (option_out_var(5) .eq. 1) then
232 if(len_trim(monitor_file) .ne. 70) then
233 monitor_file5 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor5
234 else
235 monitor_file5 = file_monitor5
236 endif
237 allocate(variables_5(0:6*count_mon))
238 open(unit_monitor5,file=monitor_file5,position='APPEND')
239 variables_5(0) = tt1
240 endif
241 if (option_out_var(6) .eq. 1) then
242 if(len_trim(monitor_file) .ne. 70) then
243 monitor_file6 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor6
244 else
245 monitor_file6 = file_monitor6
246 endif
247 allocate(variables_6(0:3*count_mon))
248 open(unit_monitor6,file=monitor_file6,position='APPEND')
249 variables_6(0) = tt1
250 endif
251
252 if (dbg .eq. 1) then
253 if(len_trim(monitor_file) .ne. 70) then
254 monitor_file7 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor7
255 monitor_file8 = monitor_file(1:len_trim(monitor_file)) // '/' // file_monitor8
256 else
257 monitor_file7 = file_monitor7
258 monitor_file8 = file_monitor8
259 endif
260 allocate(variables_7(0:count_mon),variables_8(0:count_mon))
261 open(unit_monitor7,file=monitor_file7,position='APPEND')
262 open(unit_monitor8,file=monitor_file8,position='APPEND')
263 variables_7(0) = tt1; variables_8(0) = tt1
264
265
266 endif
267
268
269
270 ishift = 0
271 jshift = 0
272 kshift = 0
273
274 do imon = 1, nmonitlst
275
276 ielem = elem_mlst(imon) !ie = index hexahedra containing monitor
277 call get_indloc_from_indglo(local_el_num, ne_loc, ielem, ie)
278 if (ie .ne. 0) then
279
280 im = cs_loc(cs_loc(ie -1) +0)
281 nn = sdeg_mat(im) +1
282
283 allocate(ct(nn),ww(nn),dd(nn,nn))
284 allocate(ux_el(nn,nn,nn),uy_el(nn,nn,nn),uz_el(nn,nn,nn))
285 allocate(variable1_el(nn,nn,nn),variable2_el(nn,nn,nn),variable3_el(nn,nn,nn))
286 allocate(variable4_el(nn,nn,nn),variable5_el(nn,nn,nn),variable6_el(nn,nn,nn))
287 call make_lgl_nw(nn,ct,ww,dd)
288
289 do k = 1,nn
290 do j = 1,nn
291 do i = 1,nn
292 is = nn*nn*(k -1) +nn*(j -1) +i
293 in = cs_loc(cs_loc(ie -1) + is)
294
295 iaz = 3*(in -1) +1
296 ux_el(i,j,k) = u1(iaz)
297 iaz = 3*(in -1) +2
298 uy_el(i,j,k) = u1(iaz)
299 iaz = 3*(in -1) +3
300 uz_el(i,j,k) = u1(iaz)
301 enddo
302 enddo
303 enddo
304
305 if (option_out_var(1).eq.1) then
306 !-------------------------------------------------------------
307 ! DISPLACEMENT
308 !-------------------------------------------------------------
309
310 call get_monitor_value(nn,ct,ux_el,&
311 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uxm)
312
313 call get_monitor_value(nn,ct,uy_el,&
314 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uym)
315
316 call get_monitor_value(nn,ct,uz_el,&
317 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),uzm)
318
319 if (dabs(uxm).lt.1.0e-30) uxm = 0.0e+00
320 if (dabs(uym).lt.1.0e-30) uym = 0.0e+00
321 if (dabs(uzm).lt.1.0e-30) uzm = 0.0e+00
322
323
324 variables_1(ishift+1) = uxm
325 variables_1(ishift+2) = uym
326 variables_1(ishift+3) = uzm
327 !-------------------------------------------------------------
328 endif
329
330 if (option_out_var(2).eq.1) then
331 !-------------------------------------------------------------
332 ! VELOCITY
333 !-------------------------------------------------------------
334 do k = 1,nn
335 do j = 1,nn
336 do i = 1,nn
337 is = nn*nn*(k -1) +nn*(j -1) +i
338 in = cs_loc(cs_loc(ie -1) + is)
339
340 iaz = 3*(in -1) +1
341 ux_el(i,j,k) = (u2(iaz) - u0(iaz)) / (2.0d0*dt)
342 iaz = 3*(in -1) +2
343 uy_el(i,j,k) = (u2(iaz) - u0(iaz)) / (2.0d0*dt)
344 iaz = 3*(in -1) +3
345 uz_el(i,j,k) = (u2(iaz) - u0(iaz)) / (2.0d0*dt)
346 enddo
347 enddo
348 enddo
349
350 call get_monitor_value(nn,ct,ux_el,&
351 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),vxm)
352
353 call get_monitor_value(nn,ct,uy_el,&
354 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),vym)
355
356 call get_monitor_value(nn,ct,uz_el,&
357 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),vzm)
358
359 if (dabs(vxm).lt.1.0e-30) vxm = 0.0e+00
360 if (dabs(vym).lt.1.0e-30) vym = 0.0e+00
361 if (dabs(vzm).lt.1.0e-30) vzm = 0.0e+00
362
363
364 variables_2(ishift+1) = vxm
365 variables_2(ishift+2) = vym
366 variables_2(ishift+3) = vzm
367 !-------------------------------------------------------------
368 endif
369
370 if (option_out_var(3).eq.1) then
371 !-------------------------------------------------------------
372 ! ACCELERATION
373 !-------------------------------------------------------------
374 do k = 1,nn
375 do j = 1,nn
376 do i = 1,nn
377 is = nn*nn*(k -1) +nn*(j -1) +i
378 in = cs_loc(cs_loc(ie -1) + is)
379
380 iaz = 3*(in -1) +1
381 ux_el(i,j,k) = (u2(iaz) -2.0*u1(iaz) +u0(iaz)) / dt2
382 iaz = 3*(in -1) +2
383 uy_el(i,j,k) = (u2(iaz) -2.0*u1(iaz) +u0(iaz)) / dt2
384 iaz = 3*(in -1) +3
385 uz_el(i,j,k) = (u2(iaz) -2.0*u1(iaz) +u0(iaz)) / dt2
386 enddo
387 enddo
388 enddo
389
390 call get_monitor_value(nn,ct,ux_el,&
391 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),axm)
392
393 call get_monitor_value(nn,ct,uy_el,&
394 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),aym)
395
396 call get_monitor_value(nn,ct,uz_el,&
397 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),azm)
398
399 if (dabs(axm).lt.1.0e-30) axm = 0.0e+00
400 if (dabs(aym).lt.1.0e-30) aym = 0.0e+00
401 if (dabs(azm).lt.1.0e-30) azm = 0.0e+00
402
403
404 variables_3(ishift+1) = axm
405 variables_3(ishift+2) = aym
406 variables_3(ishift+3) = azm
407 !-------------------------------------------------------------
408 endif
409
410 if (option_out_var(4).eq.1) then
411 !-------------------------------------------------------------
412 ! STRESS
413 !-------------------------------------------------------------
414 do k = 1,nn
415 do j = 1,nn
416 do i = 1,nn
417 is = nn*nn*(k -1) +nn*(j -1) +i
418 in = cs_loc(cs_loc(ie -1) + is)
419
420 iaz = 6*(in -1) +1
421 variable1_el(i,j,k) = stress(iaz)
422 iaz = 6*(in -1) +2
423 variable2_el(i,j,k) = stress(iaz)
424 iaz = 6*(in -1) +3
425 variable3_el(i,j,k) = stress(iaz)
426 iaz = 6*(in -1) +4
427 variable4_el(i,j,k) = stress(iaz)
428 iaz = 6*(in -1) +5
429 variable5_el(i,j,k) = stress(iaz)
430 iaz = 6*(in -1) +6
431 variable6_el(i,j,k) = stress(iaz)
432 enddo
433 enddo
434 enddo
435
436 call get_monitor_value(nn,ct,variable1_el,&
437 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable1m)
438 call get_monitor_value(nn,ct,variable2_el,&
439 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable2m)
440 call get_monitor_value(nn,ct,variable3_el,&
441 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable3m)
442 call get_monitor_value(nn,ct,variable4_el,&
443 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable4m)
444 call get_monitor_value(nn,ct,variable5_el,&
445 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable5m)
446 call get_monitor_value(nn,ct,variable6_el,&
447 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable6m)
448
449 if (dabs(variable1m).lt.1.0e-30) variable1m = 0.0e+00
450 if (dabs(variable2m).lt.1.0e-30) variable2m = 0.0e+00
451 if (dabs(variable3m).lt.1.0e-30) variable3m = 0.0e+00
452 if (dabs(variable4m).lt.1.0e-30) variable4m = 0.0e+00
453 if (dabs(variable5m).lt.1.0e-30) variable5m = 0.0e+00
454 if (dabs(variable6m).lt.1.0e-30) variable6m = 0.0e+00
455
456 ! Instability control
457 ! Check if one of the monitored values is out of bounds
458 if (b_instabilitycontrol) then
459 if (dabs(variable1m) .gt. instability_maxval .or. dabs(variable2m) .gt. instability_maxval .or. &
460 dabs(variable3m) .gt. instability_maxval .or. dabs(variable4m) .gt. instability_maxval .or. &
461 dabs(variable5m) .gt. instability_maxval .or. dabs(variable6m) .gt. instability_maxval) then
462 write(*,*) '+======================================================================================+'
463 write(*,'(A,E12.4,A)') ' | Instability control: monitored stress out of bounds (maxval=', instability_maxval, '), aborting! |'
464 write(*,*) '+======================================================================================+'
465 b_instability_abort = .true.
466 return
467 endif
468 endif
469
470 variables_4(jshift+1) = variable1m
471 variables_4(jshift+2) = variable2m
472 variables_4(jshift+3) = variable3m
473 variables_4(jshift+4) = variable4m
474 variables_4(jshift+5) = variable5m
475 variables_4(jshift+6) = variable6m
476
477 !-------------------------------------------------------------
478 endif
479
480 if (option_out_var(5).eq.1) then
481 !-------------------------------------------------------------
482 ! STRAIN
483 !-------------------------------------------------------------
484 do k = 1,nn
485 do j = 1,nn
486 do i = 1,nn
487 is = nn*nn*(k -1) +nn*(j -1) +i
488 in = cs_loc(cs_loc(ie -1) + is)
489
490 iaz = 6*(in -1) +1
491 variable1_el(i,j,k) = strain(iaz)
492 iaz = 6*(in -1) +2
493 variable2_el(i,j,k) = strain(iaz)
494 iaz = 6*(in -1) +3
495 variable3_el(i,j,k) = strain(iaz)
496 iaz = 6*(in -1) +4
497 variable4_el(i,j,k) = strain(iaz)
498 iaz = 6*(in -1) +5
499 variable5_el(i,j,k) = strain(iaz)
500 iaz = 6*(in -1) +6
501 variable6_el(i,j,k) = strain(iaz)
502 enddo
503 enddo
504 enddo
505
506 call get_monitor_value(nn,ct,variable1_el,&
507 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable1m)
508
509 call get_monitor_value(nn,ct,variable2_el,&
510 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable2m)
511
512 call get_monitor_value(nn,ct,variable3_el,&
513 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable3m)
514
515 call get_monitor_value(nn,ct,variable4_el,&
516 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable4m)
517
518 call get_monitor_value(nn,ct,variable5_el,&
519 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable5m)
520
521 call get_monitor_value(nn,ct,variable6_el,&
522 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable6m)
523
524 if (dabs(variable1m).lt.1.0e-30) variable1m = 0.0e+00
525 if (dabs(variable2m).lt.1.0e-30) variable2m = 0.0e+00
526 if (dabs(variable3m).lt.1.0e-30) variable3m = 0.0e+00
527 if (dabs(variable4m).lt.1.0e-30) variable4m = 0.0e+00
528 if (dabs(variable5m).lt.1.0e-30) variable5m = 0.0e+00
529 if (dabs(variable6m).lt.1.0e-30) variable6m = 0.0e+00
530
531
532 variables_5(jshift+1) = variable1m
533 variables_5(jshift+2) = variable2m
534 variables_5(jshift+3) = variable3m
535 variables_5(jshift+4) = variable4m
536 variables_5(jshift+5) = variable5m
537 variables_5(jshift+6) = variable6m
538
539 !-------------------------------------------------------------
540 endif
541
542 if (option_out_var(6).eq.1) then
543 !-------------------------------------------------------------
544 ! OMEGA
545 !-------------------------------------------------------------
546 do k = 1,nn
547 do j = 1,nn
548 do i = 1,nn
549 is = nn*nn*(k -1) +nn*(j -1) +i
550 in = cs_loc(cs_loc(ie -1) + is)
551
552 iaz = 3*(in -1) +1
553 variable1_el(i,j,k) = omega(iaz)
554 iaz = 3*(in -1) +2
555 variable2_el(i,j,k) = omega(iaz)
556 iaz = 3*(in -1) +3
557 variable3_el(i,j,k) = omega(iaz)
558 enddo
559 enddo
560 enddo
561
562 call get_monitor_value(nn,ct,variable1_el,&
563 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable1m)
564
565 call get_monitor_value(nn,ct,variable2_el,&
566 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable2m)
567
568 call get_monitor_value(nn,ct,variable3_el,&
569 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable3m)
570
571 if (dabs(variable1m).lt.1.0e-30) variable1m = 0.0e+00
572 if (dabs(variable2m).lt.1.0e-30) variable2m = 0.0e+00
573 if (dabs(variable3m).lt.1.0e-30) variable3m = 0.0e+00
574
575 variables_6(ishift+1) = variable1m
576 variables_6(ishift+2) = variable2m
577 variables_6(ishift+3) = variable3m
578
579 endif
580
581 if (dbg.eq.1) then
582 !-------------------------------------------------------------
583 ! MU, GAMMA NLE
584 !-------------------------------------------------------------
585 do k = 1,nn
586 do j = 1,nn
587 do i = 1,nn
588 is = nn*nn*(k -1) +nn*(j -1) +i
589 in = cs_loc(cs_loc(ie -1) + is)
590
591
592 variable1_el(i,j,k) = mu(in)
593 variable2_el(i,j,k) = gamma(in)
594 enddo
595 enddo
596 enddo
597
598 call get_monitor_value(nn,ct,variable1_el,&
599 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable1m)
600
601 call get_monitor_value(nn,ct,variable2_el,&
602 xr_mlst(imon),yr_mlst(imon),zr_mlst(imon),variable2m)
603
604
605 if (dabs(variable1m).lt.1.0e-30) variable1m = 0.0e+00
606 if (dabs(variable2m).lt.1.0e-30) variable2m = 0.0e+00
607
608
609 variables_7(kshift+1) = variable1m
610 variables_8(kshift+1) = variable2m
611
612 endif
613
614 deallocate(ct,ww,dd)
615 deallocate(ux_el,uy_el,uz_el)
616 deallocate(variable1_el,variable2_el,variable3_el)
617 deallocate(variable4_el,variable5_el,variable6_el)
618 ishift = ishift + 3
619 jshift = jshift + 6
620 kshift = kshift + 1
621
622 endif
623
624
625 enddo
626
627
628
629
630 if (option_out_var(1) .eq. 1) then
631 write(unit_monitor1,*) variables_1
632 close(unit_monitor1)
633 deallocate(variables_1)
634 endif
635 if (option_out_var(2) .eq. 1) then
636 write(unit_monitor2,*) variables_2
637 close(unit_monitor2)
638 deallocate(variables_2)
639 endif
640 if (option_out_var(3) .eq. 1) then
641 write(unit_monitor3,*) variables_3
642 close(unit_monitor3)
643 deallocate(variables_3)
644 endif
645 if (option_out_var(4) .eq. 1) then
646 write(unit_monitor4,*) variables_4
647 close(unit_monitor4)
648 deallocate(variables_4)
649 endif
650 if (option_out_var(5) .eq. 1) then
651 write(unit_monitor5,*) variables_5
652 close(unit_monitor5)
653 deallocate(variables_5)
654 endif
655 if (option_out_var(6) .eq. 1) then
656 write(unit_monitor6,*) variables_6
657 close(unit_monitor6)
658 deallocate(variables_6)
659 endif
660
661
662
663 if (dbg .eq. 1) then
664 write(unit_monitor7,*) variables_7
665 close(unit_monitor7)
666 deallocate(variables_7)
667 write(unit_monitor8,*) variables_8
668 close(unit_monitor8)
669 deallocate(variables_8)
670 endif
671
672
673
subroutine get_indloc_from_indglo(local_el, nel_loc, ie, ic)
Returns local id from global id.
subroutine get_monitor_value(nb_nod, xq, val, xref, yref, zref, re
Computes the mean value.
subroutine make_lgl_nw(nb_pnt, xq, wq, dd)
Makes Gauss-Legendre-Lobatto nodes, weigths and spectral derivatives.

References get_indloc_from_indglo(), get_monitor_value(), and make_lgl_nw().

Here is the call graph for this function: