ElmerFoamFSI  2.0
ElmerFoamFSI is fluid-solid interaction simulation application built up from OpenFOAM CFD and Elmer CSM coupled through the IMPACT multiphysics software integration infrastructure.
 All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Groups Pages
TimeModule.F90
Go to the documentation of this file.
1 !/*****************************************************************************/
2 ! *
3 ! * Elmer, A Finite Element Software for Multiphysical Problems
4 ! *
5 ! * Copyright 1st April 1995 - , CSC - IT Center for Science Ltd., Finland
6 ! *
7 ! * This library is free software; you can redistribute it and/or
8 ! * modify it under the terms of the GNU Lesser General Public
9 ! * License as published by the Free Software Foundation; either
10 ! * version 2.1 of the License, or (at your option) any later version.
11 ! *
12 ! * This library is distributed in the hope that it will be useful,
13 ! * but WITHOUT ANY WARRANTY; without even the implied warranty of
14 ! * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
15 ! * Lesser General Public License for more details.
16 ! *
17 ! * You should have received a copy of the GNU Lesser General Public
18 ! * License along with this library (in file ../LGPL-2.1); if not, write
19 ! * to the Free Software Foundation, Inc., 51 Franklin Street,
20 ! * Fifth Floor, Boston, MA 02110-1301 USA
21 ! *
22 ! *****************************************************************************/
23 !
24 !/******************************************************************************
25 ! *
26 ! * ELMER/FEM Solver main program
27 ! *
28 ! ******************************************************************************
29 ! *
30 ! * Authors: Juha Ruokolainen
31 ! * Email: Juha.Ruokolainen@csc.fi
32 ! * Web: http://www.csc.fi/elmer
33 ! * Address: CSC - IT Center for Science Ltd.
34 ! * Keilaranta 14
35 ! * 02101 Espoo, Finland
36 ! *
37 ! * Original Date: 02 Jun 1997
38 ! *
39 ! *****************************************************************************/
40 
42 
44 
46 
48 
51 
52 !------------------------------------------------------------------------------
54 !------------------------------------------------------------------------------
55  MODULE timemodule
56 !------------------------------------------------------------------------------
57 
58  USE generalmodule
59 
60 !------------------------------------------------------------------------------
61  IMPLICIT NONE
62 !------------------------------------------------------------------------------
63  REAL(KIND=dp) :: ddt
64  INTEGER :: timeleft,cum_timestep
65  INTEGER, SAVE :: stepcount=0, RealTimestep
66  LOGICAL :: SteadyStateReached=.FALSE.
67 
68  REAL(KIND=dp) :: CumTime, MaxErr, AdaptiveLimit, &
69  AdaptiveMinTimestep, AdaptiveMaxTimestep, timePeriod
70  INTEGER :: SmallestCount, AdaptiveKeepSmallest, StepControl=-1
71  LOGICAL :: AdaptiveTime = .TRUE.
72 
73  REAL(KIND=dp) :: newtime, prevtime=0, maxtime, exitcond
74  REAL(KIND=dp), ALLOCATABLE :: xx(:,:), xxnrm(:), yynrm(:), PrevXX(:,:,:)
75 
76  !Something I (Jess) am adding in order to see if I can access
77  !the displacements from this level
78  TYPE(valuelist_t), POINTER :: SolverParams
79  TYPE(variable_t), POINTER :: StressSol
80  CHARACTER(LEN=MAX_NAME_LEN) :: Equation
81  REAL(KIND=dp), POINTER :: Displacement(:)
82  INTEGER :: BoundaryElementCount, ElementCount, body_id
83  INTEGER :: bc_id, nElementNodes, nt, nk
84  INTEGER, POINTER :: MyIndex(:), MyNodeIndexes(:), MyPerm(:)
85  TYPE(element_t), POINTER :: Element, MyCurrentElement
86  TYPE(nodes_t), SAVE :: ElementNodes
87  TYPE(mesh_t), POINTER :: MyMesh
88  LOGICAL :: IsFSI
89  DOUBLE PRECISION :: FinalTime, PreviousTime
90  !End of Jess stuff
91 
92 !------------------------------------------------------------------------------
93  CONTAINS
94 !------------------------------------------------------------------------------
95 
96  SUBROUTINE updateloads(global,runs)
97  USE testobject
98  USE lists
99 
100  IMPLICIT NONE
101 
102  include 'comf90.h'
103 
104  TYPE(t_global), POINTER :: global
105  INTEGER :: runs
106  REAL(KIND=dp), ALLOCATABLE :: f(:)
107  INTEGER :: myn, currentinterval
108  TYPE(valuelist_t), POINTER :: ptr
109 
110  WRITE(6,*) 'MyTimeModule:UpdateLoads: Updating loads on the structure'
111 
112  IF (myverbosity > 3) THEN
113  WRITE(6,*) 'sTime(1) = ', stime(1)
114  WRITE(6,*) 'FinalTime = ', finaltime
115  WRITE(6,*) 'PreviousTime = ', previoustime
116  END IF
117 
118  !printing the loads as a check
119  IF( myverbosity > 3) THEN
120  WRITE(*,*) 'global%NodeLoads:'
121  DO t = 1, global%nNodes
122  WRITE(*,*) global%NodeLoads(3*(t-1) + 1), global%NodeLoads(3*(t-1) + 2), &
123  global%NodeLoads(3*(t-1) + 3)
124  END DO
125  END IF
126  IF( myverbosity > 3) THEN
127  WRITE(*,*) 'global%PreviousLoads:'
128  DO t = 1, global%nNodes
129  DO j =1,3
130  WRITE(*,*) global%PreviousLoads(j,t)
131  END DO
132  END DO
133  END IF
134 
135  !Setting the loads accessible by Elmer to the interpolated value
136  !for the current time
137  WRITE(*,*) 'MyTimeModule:UpdateLoads: Time Step Summary '
138  WRITE(*,*) ' sTime(1) = ', stime(1)
139  WRITE(*,*) ' PreviousTime = ', previoustime
140  WRITE(*,*) ' FinalTime = ', finaltime
141  !Original
142  DO t = 1, global%nNodes
143  j=1
144  DO j =1,3
145  IF (global%IsLoadFreeNode(t)) THEN
146  !Masoud : setting node loads to zero for beam end nodes in the
147  !Heron-Turek problem
148  currentmodel % NodeLoadsPass(j,t) = 0.d0
149  WRITE(*,*) ' Node #',t,' is load free'
150  !Masoud End
151  ELSE
152  currentmodel % NodeLoadsPass(j,t) = global%PreviousLoads(j,t) + &
153  (global%NodeLoads(3*(t-1) + j) - global%PreviousLoads(j,t))&
154  *(stime(1) - previoustime)/(finaltime - previoustime)
155  END IF
156  END DO
157  END DO
158  !Original End
159 
160  !Masoud: Sending load update only
161  !DO t = 1, global%nNodes
162  ! j=1
163  ! DO j =1,3
164  ! CurrentModel % NodeLoadsPass(j,t) = global%NodeLoads(3*(t-1) + j) - global%PreviousLoads(j,t)
165  ! END DO
166  !END DO
167  !Masoud End
168 
169 
170  !printing the loads as a check
171  IF( myverbosity > 3) THEN
172  WRITE(*,*) 'CurrentModel % NodeLoadsPass:'
173  DO t = 1, global%nNodes
174  DO j =1,3
175  WRITE(*,*) currentmodel % NodeLoadsPass(j,t)
176  END DO
177  END DO
178  END IF
179 
180  WRITE(6,*) 'MyTimeModule:UpdateLoads: Finishing'
181 
182  END SUBROUTINE updateloads
183 !----------------------------------------------------------------------
184 SUBROUTINE timestepper(global,runs)
185 
186  USE generalmodule
187  USE testobject
188 
189 !------------------------------------------------------------------------------
190  IMPLICIT NONE
191 !------------------------------------------------------------------------------
192  include 'comf90.h'
193 
194  TYPE(t_global), POINTER :: global
195  INTEGER :: runs
196 
197  DO interval = 1, timeintervals
198  stepcount = stepcount + timesteps(interval)
199  END DO
200 
201  IF (myverbosity > 3) THEN
202  WRITE(*,*) 'In TimeStepper'
203  WRITE(*,*) 'TimeIntervals = ', timeintervals
204  WRITE(*,*) 'global%nNodes = ', global%nNodes
205  END IF
206 
207  cum_timestep = 0
208  ddt = 0.0d0
209  DO interval = 1,timeintervals
210 
211  IF (myverbosity > 3) THEN
212  WRITE(*,*) 'interval = ', interval
213  END IF
214 !------------------------------------------------------------------------------
215  IF ( transient .OR. scanning ) THEN
216  dt = timestepsizes(interval,1)
217  ELSE
218  dt = 1
219  END IF
220 !------------------------------------------------------------------------------
221 ! go trough number of timesteps within an interval
222 !------------------------------------------------------------------------------
223  timeperiod = listgetcreal(currentmodel % Simulation, 'Time Period',gotit)
224  IF(.NOT.gotit) timeperiod = huge(timeperiod)
225 
226 
227  realtimestep = 1
228  WRITE(*,*) 'MyTimeModule:TimeStepper: Timesteps(interval) = ', timesteps(interval)
229  DO timestep = 1,timesteps(interval)
230 
231  cum_timestep = cum_timestep + 1
232  sstep(1) = cum_timestep
233 
234  dtfunc = listgetconstreal( currentmodel % Simulation, &
235  'Timestep Function', gotit)
236  IF(gotit) THEN
237  CALL warn('ExecSimulation','Obsolite keyword > Timestep Function < , use > Timestep Size < instead')
238  ELSE
239  dtfunc = listgetcreal( currentmodel % Simulation, &
240  'Timestep Size', gotit)
241  END IF
242  IF(gotit) dt = dtfunc
243 
244 !------------------------------------------------------------------------------
245  stime(1) = stime(1) + dt
246  speriodic(1) = stime(1)
247  DO WHILE(speriodic(1) > timeperiod)
248  speriodic(1) = speriodic(1) - timeperiod
249  END DO
250 
251  ! Move the old timesteps one step down the ladder
252  IF(timestep > 1 .OR. interval > 1) THEN
253  DO i = SIZE(sprevsizes,2),2,-1
254  sprevsizes(1,i) = sprevsizes(1,i-1)
255  END DO
256  sprevsizes(1,1) = ssize(1)
257  END IF
258  ssize(1) = dt
259 
260  sinterval(1) = interval
261  IF (.NOT. transient ) steadyit(1) = steadyit(1) + 1
262 !------------------------------------------------------------------------------
263  IF ( parenv % MyPE == 0 ) THEN
264  CALL info( 'MAIN', ' ', level=3 )
265  CALL info( 'MAIN', '-------------------------------------', level=3 )
266 
267  IF ( transient .OR. scanning ) THEN
268  WRITE( message, * ) 'Time: ',trim(i2s(cum_timestep)),'/', &
269  trim(i2s(stepcount)), stime(1)
270  CALL info( 'MAIN', message, level=3 )
271 
272  newtime= realtime()
273 
274  IF( cum_timestep > 1 ) THEN
275  maxtime = listgetconstreal( currentmodel % Simulation,'Real Time Max',gotit)
276  IF( gotit ) THEN
277  WRITE( message,'(A,F8.3)') 'Fraction of real time left: ',&
278  1.0_dp-realtime() / maxtime
279  ELSE
280  timeleft = nint((stepcount-(cum_timestep-1))*(newtime-prevtime)/60._dp);
281  IF (timeleft > 120) THEN
282  WRITE( message, *) 'Estimated time left: ', &
283  trim(i2s(timeleft/60)),' hours.'
284  ELSE IF(timeleft > 60) THEN
285  WRITE( message, *) 'Estimated time left: 1 hour ', &
286  trim(i2s(mod(timeleft,60))), ' minutes.'
287  ELSE IF(timeleft >= 1) THEN
288  WRITE( message, *) 'Estimated time left: ', &
289  trim(i2s(timeleft)),' minutes.'
290  ELSE
291  WRITE( message, *) 'Estimated time left: less than a minute.'
292  END IF
293  END IF
294  CALL info( 'MAIN', message, level=3 )
295  END IF
296  prevtime = newtime
297  ELSE
298  WRITE( message, * ) 'Steady state iteration: ',cum_timestep
299  CALL info( 'MAIN', message, level=3 )
300  END IF
301 
302  CALL info( 'MAIN', '-------------------------------------', level=3 )
303  CALL info( 'MAIN', ' ', level=3 )
304  END IF
305 
306 !------------------------------------------------------------------------------
307 ! Call UpdateLoads to the get linearly interpolated load value at
308 ! the current time
309 !------------------------------------------------------------------------------
310  IF (myverbosity > 3) THEN
311  WRITE(6,*) 'timestepper timestep = ', timestep
312  WRITE(6,*) 'sTime(1) = ', stime(1)
313  WRITE(6,*) 'dtfunc = ', dtfunc
314  WRITE(6,*) 'dt = ', dt
315  WRITE(*,*) 'TimeStepper Calling UpdateLoads'
316  END IF
317  CALL updateloads(global,runs)
318 !------------------------------------------------------------------------------
319 ! Solve any and all governing equations in the system
320 !------------------------------------------------------------------------------
321  adaptivetime = listgetlogical( currentmodel % Simulation, &
322  'Adaptive Timestepping', gotit )
323 
324  IF ( transient .AND. adaptivetime ) THEN
325  adaptivelimit = listgetconstreal( currentmodel % Simulation, &
326  'Adaptive Time Error', gotit )
327 
328  IF ( .NOT. gotit ) THEN
329  WRITE( message, * ) 'Adaptive Time Limit must be given for' // &
330  'adaptive stepping scheme.'
331  CALL fatal( 'ElmerSolver', message )
332  END IF
333 
334  adaptivemaxtimestep = listgetconstreal( currentmodel % Simulation, &
335  'Adaptive Max Timestep', gotit )
336  IF ( .NOT. gotit ) adaptivemaxtimestep = dt
337  adaptivemaxtimestep = min(adaptivemaxtimestep, dt)
338 
339  adaptivemintimestep = listgetconstreal( currentmodel % Simulation, &
340  'Adaptive Min Timestep', gotit )
341 
342  adaptivekeepsmallest = listgetinteger( currentmodel % Simulation, &
343  'Adaptive Keep Smallest', gotit, minv=0 )
344 
345  n = currentmodel % NumberOfSolvers
346  j = 0
347  k = 0
348  DO i=1,n
349  solver => currentmodel % Solvers(i)
350  IF ( ASSOCIATED( solver % Variable % Values ) ) THEN
351  IF ( ASSOCIATED( solver % Variable % PrevValues ) ) THEN
352  j = max( j, SIZE( solver % Variable % PrevValues,2 ) )
353  END IF
354  k = max( k, SIZE( solver % Variable % Values ) )
355  END IF
356  END DO
357  ALLOCATE( xx(n,k), yynrm(n), xxnrm(n), prevxx( n,k,j ) )
358 
359  cumtime = 0.0d0
360  IF ( ddt == 0.0d0 .OR. ddt > adaptivemaxtimestep ) ddt = adaptivemaxtimestep
361 
362  s = stime(1) - dt
363  smallestcount = 0
364  DO WHILE( cumtime < dt-1.0d-12 )
365  ddt = min( dt - cumtime, ddt )
366 
367  DO i=1,currentmodel % NumberOFSolvers
368  solver => currentmodel % Solvers(i)
369  IF ( ASSOCIATED( solver % Variable % Values ) ) THEN
370  n = SIZE( solver % Variable % Values )
371  xx(i,1:n) = solver % Variable % Values
372  xxnrm(i) = solver % Variable % Norm
373  IF ( ASSOCIATED( solver % Variable % PrevValues ) ) THEN
374  DO j=1,SIZE( solver % Variable % PrevValues,2 )
375  prevxx(i,1:n,j) = solver % Variable % PrevValues(:,j)
376  END DO
377  END IF
378  END IF
379  END DO
380 
381  stime(1) = s + cumtime + ddt
382  ssize(1) = ddt
383  CALL solveequations( currentmodel, ddt, transient, &
384  coupledminiter, coupledmaxiter, steadystatereached, realtimestep )
385 
386 
387  maxerr = listgetconstreal( currentmodel % Simulation, &
388  'Adaptive Error Measure', gotit )
389 
390  DO i=1,currentmodel % NumberOFSolvers
391  solver => currentmodel % Solvers(i)
392  IF ( ASSOCIATED( solver % Variable % Values ) ) THEN
393  n = SIZE(solver % Variable % Values)
394  yynrm(i) = solver % Variable % Norm
395  solver % Variable % Values = xx(i,1:n)
396  IF ( ASSOCIATED( solver % Variable % PrevValues ) ) THEN
397  DO j=1,SIZE( solver % Variable % PrevValues,2 )
398  solver % Variable % PrevValues(:,j) = prevxx(i,1:n,j)
399  END DO
400  END IF
401  END IF
402  END DO
403 
404  sstep(1) = ddt / 2
405  stime(1) = s + cumtime + ddt/2
406  CALL solveequations( currentmodel, ddt/2, transient, &
407  coupledminiter, coupledmaxiter, steadystatereached, realtimestep )
408  stime(1) = s + cumtime + ddt
409  CALL solveequations( currentmodel, ddt/2, transient, &
410  coupledminiter, coupledmaxiter, steadystatereached, realtimestep )
411 
412  maxerr = abs( maxerr - listgetconstreal( currentmodel % Simulation, &
413  'Adaptive Error Measure', gotit ) )
414 
415  IF ( .NOT. gotit ) THEN
416  maxerr = 0.0d0
417  DO i=1,currentmodel % NumberOFSolvers
418  solver => currentmodel % Solvers(i)
419  IF ( ASSOCIATED( solver % Variable % Values ) ) THEN
420  IF ( yynrm(i) /= solver % Variable % Norm ) THEN
421  maxerr = max(maxerr,abs(yynrm(i)-solver % Variable % Norm)/yynrm(i))
422  END IF
423  END IF
424  END DO
425  END IF
426 
427  IF ( maxerr < adaptivelimit .OR. ddt <= adaptivemintimestep ) THEN
428  cumtime = cumtime + ddt
429  realtimestep = realtimestep+1
430  IF ( smallestcount >= adaptivekeepsmallest .OR. stepcontrol > 0 ) THEN
431  ddt = min( 2*ddt, adaptivemaxtimestep )
432  stepcontrol = 1
433  smallestcount = 0
434  ELSE
435  stepcontrol = 0
436  smallestcount = smallestcount + 1
437  END IF
438  ELSE
439  DO i=1,currentmodel % NumberOFSolvers
440  solver => currentmodel % Solvers(i)
441  IF ( ASSOCIATED( solver % Variable % Values ) ) THEN
442  n = SIZE(solver % Variable % Values)
443  solver % Variable % Norm = xxnrm(i)
444  solver % Variable % Values = xx(i,1:n)
445  IF ( ASSOCIATED( solver % Variable % PrevValues ) ) THEN
446  DO j=1,SIZE( solver % Variable % PrevValues,2 )
447  solver % Variable % PrevValues(:,j) = prevxx(i,1:n,j)
448  END DO
449  END IF
450  END IF
451  END DO
452  ddt = ddt / 2
453  stepcontrol = -1
454  END IF
455  WRITE(*,'(a,3e20.12)') 'Adaptive(cum,ddt,err): ', cumtime, ddt, maxerr
456  END DO
457  ssize(1) = dt
458  stime(1) = s + dt
459 
460  DEALLOCATE( xx, xxnrm, yynrm, prevxx )
461  ELSE ! Adaptive timestepping
462  !IF (MyVerbosity > 3) THEN
463  WRITE(*,*) 'MyTimeModule:TimeStepper: Calling SolveEquations'
464  WRITE(*,*) ' Transient = ', transient
465  !END IF
466  CALL solveequations( currentmodel, dt, transient, &
467  coupledminiter, coupledmaxiter, steadystatereached, realtimestep )
468  realtimestep = realtimestep+1
469  END IF
470 
471 !------------------------------------------------------------------------------
472 ! Save results to disk, if requested
473 !------------------------------------------------------------------------------
474  lastsaved = .false.
475  IF( outputintervals(interval) /= 0 ) THEN
476 
477  CALL savetopost(0)
478  k = mod( timestep-1, outputintervals(interval) )
479  IF ( k == 0 .OR. steadystatereached ) THEN
480 
481  DO i=1,currentmodel % NumberOfSolvers
482  solver => currentmodel % Solvers(i)
483  IF ( solver % PROCEDURE == 0 ) cycle
484  execthis = ( solver % SolverExecWhen == solver_exec_ahead_save)
485  when = listgetstring( solver % Values, 'Exec Solver', gotit )
486  IF ( gotit ) execthis = ( when == 'before saving')
487  IF( execthis ) CALL solveractivate( currentmodel,solver,dt,transient )
488  END DO
489 
490  CALL savecurrent(timestep)
491  lastsaved = .true.
492 
493  DO i=1,currentmodel % NumberOfSolvers
494  solver => currentmodel % Solvers(i)
495  IF ( solver % PROCEDURE == 0 ) cycle
496  execthis = ( solver % SolverExecWhen == solver_exec_after_save)
497  when = listgetstring( solver % Values, 'Exec Solver', gotit )
498  IF ( gotit ) execthis = ( when == 'after saving')
499  IF( execthis ) CALL solveractivate( currentmodel,solver,dt,transient )
500  END DO
501  END IF
502  END IF
503 !------------------------------------------------------------------------------
504 
505  maxtime = listgetcreal( currentmodel % Simulation,'Real Time Max',gotit)
506  IF( gotit .AND. realtime() - rt0 > maxtime ) THEN
507  CALL info('ElmerSolver','Reached allowed maximum real time, exiting...')
508  goto 100
509  END IF
510 
511  exitcond = listgetcreal( currentmodel % Simulation,'Exit Condition',gotit)
512  IF( gotit .AND. exitcond > 0.0_dp ) THEN
513  CALL info('ElmerSolver','Found a positive exit condition, exiting...')
514  goto 100
515  END IF
516 
517 !------------------------------------------------------------------------------
518 
519  IF ( steadystatereached .AND. .NOT. (transient .OR. scanning) ) THEN
520  IF ( timestep >= coupledminiter ) THEN
521  WRITE(6,*) 'SteadyStateReached, exiting'
522  EXIT
523  END IF
524  END IF
525 
526 !------------------------------------------------------------------------------
527  END DO ! timestep within an iterval
528 !------------------------------------------------------------------------------
529 
530 !------------------------------------------------------------------------------
531  END DO ! timestep intervals, i.e. the simulation
532 
533  IF (myverbosity > 3) THEN
534  write(6,*) 'LastSaved = ', lastsaved
535  END IF
536 
537  runs = 1
538 
539 100 RETURN
540 
541 END SUBROUTINE timestepper
542 !------------------------------------------------------------------------------
543  END MODULE timemodule
544 !------------------------------------------------------------------------------
545 
ElmerLib Elmer library routines
Definition: TimeModule.F90:55
subroutine savecurrent(CurrentStep)
Saves current timestep to external files.
subroutine savetopost(CurrentStep)
Saves results file to post processing file of ElmerPost format, if requested.
subroutine timestepper(global, runs)
Definition: TimeModule.F90:184
subroutine updateloads(global, runs)
Definition: TimeModule.F90:96
ElmerLib Elmer library routines