DCS
a Driven-Cavity Open source Simulator code
 All Classes Files Functions Variables Groups Pages
DCS.f90
Go to the documentation of this file.
1 
17 
23 
29 
35 
45 program dcs
46 !-----------------------------------------------------------------------------------------------------------------------------------
47 use, intrinsic:: iso_fortran_env, only: stdout => output_unit, stderr => error_unit ! Standard output/error logical units.
48 USE ir_precision ! Integers and reals precision definition.
49 USE data_type_cavity ! Definition of Type_Cavity.
50 USE data_type_conservative ! Definition of Type_Conservative.
51 !-----------------------------------------------------------------------------------------------------------------------------------
52 
53 !-----------------------------------------------------------------------------------------------------------------------------------
54 implicit none
57 type(type_cavity):: cavity
58 real(R8P):: rtol = 0.0001_r8p
59 integer(I4P):: nout = 1000_i4p
60 character(3):: oform = "tec"
62 !-----------------------------------------------------------------------------------------------------------------------------------
63 
64 !-----------------------------------------------------------------------------------------------------------------------------------
65 call dcs_initialize ! initializing the simulation
66 call dcs_simulate ! performing the simulation
67 call dcs_finalize ! finalizing the simulation
68 stop
69 !-----------------------------------------------------------------------------------------------------------------------------------
70 contains
77  integer function get_unit(Free_Unit)
78  !---------------------------------------------------------------------------------------------------------------------------------
79  implicit none
80  integer, intent(OUT), optional:: free_unit
81  integer:: n1
82  integer:: ios
83  logical:: lopen
84  !---------------------------------------------------------------------------------------------------------------------------------
85 
86  !---------------------------------------------------------------------------------------------------------------------------------
87  get_unit = -1
88  n1=1
89  do
90  if ((n1/=stdout).AND.(n1/=stderr)) then
91  inquire (unit=n1,opened=lopen,iostat=ios)
92  if (ios==0) then
93  if (.NOT.lopen) then
94  get_unit = n1 ; if (present(free_unit)) free_unit = get_unit
95  return
96  endif
97  endif
98  endif
99  n1=n1+1
100  enddo
101  return
102  !---------------------------------------------------------------------------------------------------------------------------------
103  endfunction get_unit
104 
106  subroutine print_usage()
107  !---------------------------------------------------------------------------------------------------------------------------------
108  ! Subroutine for printing the correct use of the program.
109  !---------------------------------------------------------------------------------------------------------------------------------
110 
111  !---------------------------------------------------------------------------------------------------------------------------------
112  implicit none
113  !---------------------------------------------------------------------------------------------------------------------------------
114 
115  !---------------------------------------------------------------------------------------------------------------------------------
116  write(stdout,'(A)')' DCS'
117  write(stdout,'(A)')' Driven-Cavity Simulator code'
118  write(stdout,'(A)')' Usage:'
119  write(stdout,'(A)')' ./DCS -N number_of_cells [optionals parameters]'
120  write(stdout,*)
121  write(stdout,'(A)')' Optional parameters:'
122  write(stdout,'(A)')' -Re Reynolds_number => default 500'
123  write(stdout,'(A)')' -beta over_relaxation_parameter => default 0.6'
124  write(stdout,'(A)')' -rtol residual_tolerance => default 10^-4'
125  write(stdout,'(A)')' -nout standard_output_update_frequency => default 1000 iterations'
126  write(stdout,'(A)')' -oform output_file_format => "tec" for Tecplot output or "gnu" for gnuplot one, default "tec"'
127  write(stdout,*)
128  write(stdout,'(A)')' Example: '
129  write(stdout,'(A)')' ./DCS -Re 9.d2 -beta 0.5d0 -N 256 -nout 10000 -rtol 1.d-6'
130  write(stdout,*)
131  return
132  !---------------------------------------------------------------------------------------------------------------------------------
133  endsubroutine print_usage
134 
136  subroutine dcs_initialize()
137  !---------------------------------------------------------------------------------------------------------------------------------
138  implicit none
139  real(R8P):: re
140  real(R8P):: beta
141  integer(I4P):: n
142  integer(I4P):: nca = 0
143  integer(I4P):: c
144  character(6):: ca_switch
145  character(100):: sbuf
146  !---------------------------------------------------------------------------------------------------------------------------------
147 
148  !---------------------------------------------------------------------------------------------------------------------------------
149  re = cavity%Re
150  beta = cavity%beta
151  n = cavity%mesh%N
152  ! parsing command line arguments
153  nca = command_argument_count()
154  if (nca==0) then
155  write(stderr,'(A)')' Error: no argument has been passed to command line'
156  call print_usage
157  stop
158  else
159  ! processing switch
160  c = 0
161  do while (c<nca)
162  c = c + 1
163  call get_command_argument(c, ca_switch)
164  select case(adjustl(trim(ca_switch)))
165  case('-Re')
166  call get_command_argument(c+1,sbuf) ; c = c + 1
167  read(sbuf,*)re
168  case('-beta')
169  call get_command_argument(c+1,sbuf) ; c = c + 1
170  read(sbuf,*)beta
171  case('-N')
172  call get_command_argument(c+1,sbuf) ; c = c + 1
173  read(sbuf,*)n
174  case('-rtol')
175  call get_command_argument(c+1,sbuf) ; c = c + 1
176  read(sbuf,*)rtol
177  case('-nout')
178  call get_command_argument(c+1,sbuf) ; c = c + 1
179  read(sbuf,*)nout
180  case('-oform')
181  call get_command_argument(c+1,oform) ; c = c + 1
182  case default
183  write(stderr,'(A)') ' Error: switch "'//adjustl(trim(ca_switch))//'" is unknown'
184  call print_usage
185  stop
186  endselect
187  enddo
188  endif
189  if (n==0_i4p) then
190  write(stderr,'(A)')' Error: the number of cells N must be passed as command line argument'
191  call print_usage
192  stop
193  endif
194  write(stdout,'(A)')' Some information about the precision of runnig machine'
195  call ir_print()
196  write(stdout,*)
197  write(stdout,'(A)')' Simulation parameters'
198  write(stdout,'(A)')' Re='//trim(str(n=re))
199  write(stdout,'(A)')' beta='//trim(str(n=beta))
200  write(stdout,'(A)')' N='//trim(str(n=n))
201  write(stdout,'(A)')' rtol='//trim(str(n=rtol))
202  write(stdout,'(A)')' nout='//trim(str(n=nout))
203  write(stdout,'(A)')' oform='//trim(oform)
204  write(stdout,*)
205  ! initializing cavity data
206  call cavity%initialize(re=re,beta=beta,n=n)
207  return
208  !---------------------------------------------------------------------------------------------------------------------------------
209  endsubroutine dcs_initialize
210 
212  subroutine dcs_simulate()
213  !---------------------------------------------------------------------------------------------------------------------------------
214  implicit none
215  type(type_conservative):: residual
216  integer(I4P):: n = 0_i4p
217  !---------------------------------------------------------------------------------------------------------------------------------
218 
219  !---------------------------------------------------------------------------------------------------------------------------------
220  ! successive over-relaxation (SOR) loop
221  call residual%set(s=maxr8p,v=maxr8p)
222  sor: do while(((residual%s>rtol).AND.(residual%v>rtol)))
223  ! updating time step counter
224  n = n + 1_i4p
225  ! computing new stream function
226  call computestream(cons=cavity%cons,beta=cavity%beta,dh=cavity%mesh%dh)
227  ! computing new vorticity
228  call computevorticity(cons=cavity%cons,re=cavity%Re,beta=cavity%beta,dh=cavity%mesh%dh)
229  ! computing residuals
230  residual = computeresidual(cons=cavity%cons,re=cavity%Re,dh=cavity%mesh%dh)
231  if (mod(n,nout)==0) then
232  write(stdout,'(A)')' iteration n='//trim(str(n=n))//&
233  ' residuals: s='//trim(str(n=residual%s))//' v='//trim(str(n=residual%v))
234  endif
235  enddo sor
236  write(stdout,'(A)')' Convergence achieved n='//trim(str(n=n))
237  return
238  !---------------------------------------------------------------------------------------------------------------------------------
239  endsubroutine dcs_simulate
240 
242  subroutine dcs_finalize()
243  !---------------------------------------------------------------------------------------------------------------------------------
244  implicit none
245  integer(I4P):: u
246  integer(I4P):: i,j
247  !---------------------------------------------------------------------------------------------------------------------------------
248 
249  !---------------------------------------------------------------------------------------------------------------------------------
250  ! writing solution
251  select case(trim(oform))
252  case('tec')
253  ! tecplot format
254  open(unit=get_unit(u),file='DCS_out.tec')
255  write(u,'(A)')'VARIABLES="x" "y" "s" "v"'
256  write(u,'(A)')'ZONE T="Driven Cavity" I='//trim(str(n=cavity%mesh%N+1))//' J='//trim(str(n=cavity%mesh%N+1))
257  do j=0,cavity%mesh%N
258  do i=0,cavity%mesh%N
259  write(u,'(A)')trim(str(n=cavity%mesh%x(i)))//' '//trim(str(n=cavity%mesh%y(j)))//' '//&
260  trim(str(n=cavity%cons(i,j)%s))//' '//trim(str(n=cavity%cons(i,j)%v))
261  enddo
262  enddo
263  close(u)
264  case('gnu')
265  ! gnuplot format
266  open(unit=get_unit(u),file='DCS_out.gnu')
267  do j=0,cavity%mesh%N
268  do i=0,cavity%mesh%N
269  write(u,'(A)')trim(str(n=cavity%mesh%x(i)))//' '//trim(str(n=cavity%mesh%y(j)))//' '//&
270  trim(str(n=cavity%cons(i,j)%s))//' '//trim(str(n=cavity%cons(i,j)%v))
271  enddo
272  write(u,*)
273  enddo
274  close(u)
275  endselect
276  ! finalizing cavity data
277  call cavity%finalize
278  return
279  !---------------------------------------------------------------------------------------------------------------------------------
280  endsubroutine dcs_finalize
282 endprogram dcs
subroutine dcs_simulate()
Subroutine for simulating drive cavity problems.
Definition: DCS.f90:265
pure type(type_conservative) function, public computeresidual(cons, Re, dh)
Function for computing residuals.
subroutine print_usage()
Subroutine for printing to stdout the correct usage of the code.
Definition: DCS.f90:159
This module contains the definition of Type_Cavity and its procedures.
Derived type containing conservative variables.
pure subroutine, public computevorticity(cons, Re, beta, dh)
Subroutine for computing new (n+1) vorticity.
pure subroutine, public computestream(cons, beta, dh)
Subroutine for computing new (n+1) stream function.
Procedure for converting number, real and integer, to string (number to string type casting); logical...
integer function get_unit(Free_Unit)
The Get_Unit function returns a free logic unit for opening a file.
Definition: DCS.f90:130
program dcs
DCS is an Open source program for simulating driven cavity problems.
Definition: DCS.f90:98
subroutine dcs_initialize()
Subroutine for initializing the simulation according to the input options.
Definition: DCS.f90:189
subroutine dcs_finalize()
Subroutine for finalizing the simulation.
Definition: DCS.f90:295
subroutine, public ir_print(myrank, Nproc)
Subroutine for printing to the standard output the kind definition of reals and integers and the util...
real(r8p), parameter, public maxr8p
Min and max values of kind=R8P variable.
This module contains the definition of Type_Conservative and its procedures.
Derived type containing conservative variables.
Module IR_Precision makes available some portable kind-parameters and some useful procedures to deal ...