-
Notifications
You must be signed in to change notification settings - Fork 3
/
Copy pathmodule_mesh.f90
424 lines (330 loc) · 15.5 KB
/
module_mesh.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
module mesh
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!1
!>Module : Mesh Generation
!>Description
!> @ Author Alvaro
!> @ Co-author & Documentation Akshay
!> This is a module to for mesh generation and it was use three modules to perform its working completly
use newtonmod
!> This is the permission given to the main program to have an access to your module and this module basically deals with the local stretching.
use precision
use read_file_module
!> This is a module that read the data from a file and introduce it in the variables.
implicit none
!> This implicit none statement forces the programmer to declare all the variables which is considered as a good style .
contains
subroutine raw_mesh ()
real::smallalfa, dalfa, L, xinicio, xfin, factor
integer::N, M, k, dx, decision, dimxnuevo, inicio, fin
!> N amd M are integers
!> also N is number of point in x
!>also M is number of point in Y
integer :: i,counter
!>i and counter are also defined as integers
integer :: j ,t
!> j and t are defines as integers
integer :: param,poli
!>these are the function used in the main program and defined as integers
character(len=50)::filepuntos
!>filepuntos is a file that will read the data from a file and introduce it into a variable.
real,allocatable::x(:)
!> represents the value of x in the program and also it allocates it in a row/line
real,allocatable::y(:)
!> represents the value of y in the program and also it allocates it in a row/line
real,allocatable::y2(:)
!> represents the value of y2 in the program and also it allocates it in a row/line
real,allocatable::xbig(:)
!> represents the value of xbig in the program and also it allocates it in a row/line
real,allocatable::ybig(:)
!> represents the value of ybig in the program and also it allocates it in a row/line
real,allocatable::zbig(:)
!> represents the value of zbig in the program and also it allocates it in a row/line
real,allocatable::d(:)
!> represents the value of d in the program and also it allocates it in a row/line
real,allocatable::c(:)
!> represents the value of c in the program and also it allocates it in a row/line
real,allocatable::alfa(:)
!> represents the value of alfa in the program and also it allocates it in a row/line
real,allocatable::b(:)
!> represents the value of b in the program and also it allocates it in a row/line
real,allocatable:: xnuevo(:)
!> represents the value of b in the program and also it allocates it in a row/line
real,allocatable:: ynuevo(:)
!> represents the value of b in the program and also it allocates it in a row/line
real,allocatable:: y2nuevo(:)
!> represents the value of b in the program and also it allocates it in a row/line
real, allocatable :: xtotal(:)
!> represents the value of xtotal in the program and also it allocates it in a row/line
real, allocatable :: ytotal(:)
!> represents the value of ytotal in the program and also it allocates it in a row/line
real, allocatable :: y2total(:)
!> represents the value of y2total in the program and also it allocates it in a row/line
real, allocatable:: z1(:)
!> represents the value of z1 in the program and also it allocates it in a row/line
real, allocatable:: z2(:)
!> represents the value of z2 in the program and also it allocates it in a row/line
real, allocatable:: z3(:)
!> represents the value of z3 in the program and also it allocates it in a row/line
real, allocatable:: z4(:)
!> represents the value of z4 in the program and also it allocates it in a row/line
character(len=20) :: nameprogr
type vector
!>The real power of derived types comes with the ability to choose between functions(or subroutines) based on type of their arguements
real, allocatable, dimension(:)::xbig
!>!We define the array vector to introduce in it thr result of the mesh generating, before writing it in a file and store in an array so called x big
real, allocatable, dimension(:)::ybig
!>We define the array vector to introduce in it thr result of the mesh generating, before writing it in a file and store it in another array called ybig
real, allocatable, dimension(:)::zbig
!>We define the array vector to introduce in it thr result of the mesh generating, before writing it in a file and store it in another array so called zbig
end type vector
type(vector):: global
!>!>The real power of derived types comes with the ability to choose between functions(or subroutines) based on type of their arguements
print*, 'Introduce the numbers of points do you want in the vertical discretization ?'
!> Ask the user thet how many points you wants in vertical discritisation
read*, M
!> M is the number of point in y
!>Calling of the subroutine to be integrated with main program,this will read the data provided by user
!We call to the read_file subroutine to introduce in out variable the data given by the user in a file.
call read_file(filepuntos,x,y,y2,N)
!> This is the permissiom given to the module to call the subroutine into the module and module can be accessed from main program
print*, 'Your x, y, and y2 co-ordinates are:'
!> this will print the value of x, y and y2 for the number of discritisation points that the user gives
!> A simple loop which shows that i can take any values from 1 to N
do i=1, N
print*, x(i), y(i), y2(i)
!> this will print the value of x, y and y2
end do
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! Local streching:
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!local streching: as the distribution of points in 'x' direction is given by the file of the user, we give him the oportunity of increasing the number of points in a range between two points that the user choose.
print*, 'do you want to do any local streching in a longitude interval? write 1 for yes or 2 for no'
!> This allow user to input either they want local stretching or not
!=======
!>We call the read_file subroutine to introduce in out variable the data given by the user in a file.
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
read*, decision
!> This will read the decision input by user either it is 1 or 2
if (decision==1) then
!> If its 1 value goes from x(1) to x(N )
print*, 'your interval goes from ', x(1), 'to', x(N), '. Write the two values of the'
print*, 'interval you want to make a local streching. First value:'
!> This will ask the user to enter the first point where u want local stretching
read*, xinicio
print*, 'Second value:'
!> This will ask the user to enter the second point where u want local stretching
read*, xfin
!> xfin will read the first point inserted by the user for the local stretching
elseif (decision==2) then
!> This indicates if user does not wants strecthing then press 2
else
print*, 'wrong number, come on, it is not so difficult'
stop
end if
!To create a local streching, the user can increase the number of points in the selected interval by a factor proportional to the number of points that exist in that interval.
if (decision==1) then
!> This enable user to enter the factor by which they wants local stretching
print*, 'Introduce a factor to increase the number of points in this inteval, proportional to the amount of points of your curve'
!> ask the user to insert the factor
read*, factor
!> read the factor inserted by the user
!I round off the points that the user gives to the closest without losing part of the interval (the left next one of the first and the right nex one of the second)
!>A simple loop to show how the increment function is going to work
do j=1,2
do i=1,N
if (j==1) then
if (x(i)>xinicio) then
!> if x(i) is greater then (xinicio) then the first value of stretching point is equal to i-1
if (i>1) then
inicio=i-1
!>represents second value is equal to i-1
exit
else
inicio=i
exit
end if
else
end if
else
if (x(i)>(xfin-0.001)) then
!> if x(i) is greater then (xfin-0.001) then the second value of stretching point is equal to i
fin=i
!> represents second value is equal to i
exit
else
end if
end if
end do
end do
xinicio=x(inicio)
!> represents xinicio is equal to x of inicio
xfin=x(fin)
!> represents xinicio is equal to x of inicio
!print*, 'inicio es', inicio, 'y fin es', fin, 'y factor es', factor
print*, 'inicio es', inicio
!> prints inicio es as inicio
print*, 'y fin es', fin
!> prints y fin as fin
print*, 'y factor es', factor
!> prints y factor es as factor
dimxnuevo = int(factor*(fin-inicio-1))
!> represents dimxnuevo can be roughly estimated as int(factor*(fin-inicio-1))
print*, 'dimxnuevo es', dimxnuevo
!> prints the value of dimxnuevo is, dimxnuevo
!Newton
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!>call of another subroutine to be integrated with main program
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!To obtain points in the interval selected, it is neccesary to aproximate the curves given by points with a Newton polynomial.
call newton(x, y, y2, N, inicio, fin, xinicio, xfin, xnuevo, ynuevo, y2nuevo, dimxnuevo)
!> This is the permissiom given to the module to call the subroutine into the module and module can be accessed from main program
print*, 'el vector xnuevo es y su dimension', size(xnuevo)
do i=1,dimxnuevo
print*, xnuevo(i), ynuevo(i)
end do
!If the user wants to make a local streching, it is neccesary to redefine the dimension of the variables, as follows:
allocate (xtotal(inicio-1+dimxnuevo+(N-fin+1)), ytotal(inicio-1+dimxnuevo+(N-fin+1)), y2total(inicio-1+dimxnuevo+(N-fin+1)))
print*, 'la dimension de xtotal es', size(xtotal)
!Now with the new points obtained with the Newton polynomial and the previous ones, we need to rebuild the vectors with the points as follow:
counter=1
do i=1,inicio-1
xtotal(counter)=x(i)
ytotal(counter)=y(i)
y2total(counter)=y2(i)
counter=counter+1
end do
do i=1,dimxnuevo
xtotal(counter)=xnuevo(i)
ytotal(counter)=ynuevo(i)
y2total(counter)=y2nuevo(i)
counter=counter+1
end do
do i=1,(N-fin+1)
xtotal(counter)=x(fin-1+i)
ytotal(counter)=y(fin-1+i)
y2total(counter)=y2(fin-1+i)
counter=counter+1
end do
!We plot the new vectors of points.
print*, 'the dimension of your new vector is', counter-1, 'and your new vector is:'
print*, '_____x_________________y1________________y2______________coordenate'
do i=1, counter-1
print*, xtotal(i)
print*, ytotal(i)
print*, y2total(i)
print*, i
end do
!As the size of the vectors has changed, we also need to redefine the size of the array that we defined at the beginning.
N=size(xtotal)
allocate(xbig(N*M), ybig(N*M), global%xbig(N*M), global%ybig(N*M), global%zbig(N*M))
else
end if
!The next 30 lines are going to call to the subroutine that the user chooses, to generate the vertical mesh. reading an integer number from the screen. The possible distribution of points are: Chebyshev distribution, arcsen distribution, hyperbolic tangent distribution or linear one.
print*, 'for the global stretching (vertically),'
print*, 'introduce the value 1 for a Chevyshchev distribution, 2 for an arcsen distribution,'
print*, '3 for a tanh distribution, or 4 for a linear distribution'
read*, param
if (param==1) then
if (decision==1) then
!> Calling the subroutine chevy for the distribution of points
call chevy(xbig, ybig, zbig, xtotal, ytotal, y2total, M, N)
else
!> Calling the subroutine chevy for the distribution of points
call chevy(xbig, ybig, zbig, x, y, y2, M, N)
end if
elseif (param==2) then
if (decision==1) then
!>Calling of subroutine for arcsen disribution
call arcsen(xbig, ybig, zbig, xtotal, ytotal, y2total, M, N)
else
!> Calling the subroutine arcsen for the distribution of points
call arcsen(xbig, ybig, zbig, x, y, y2, M, N)
end if
elseif (param==3) then
if (decision==1) then
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!>Calling of subroutine for tanhip distribution
call tanhip(xbig, ybig, zbig, xtotal, ytotal, y2total, M, N)
else
!> Calling the subroutine tanhip for the distribution of points
call tanhip(xbig, ybig, zbig, x, y, y2, M, N)
end if
elseif (param==4) then
if (decision==1) then
!> Calling the subroutine linear for the distribution of points
call linear(xbig, ybig, zbig, xtotal, ytotal, y2total, M, N)
else
!> Calling the subroutine linear for the distribution of points
call linear(xbig, ybig, zbig, x, y, y2, M, N)
end if
else
print*, 'wrong number, come on, it is not so difficult'
stop
end if
!We introduce the results in the array:
global%xbig=xbig
!> introduction of final result in an array xbig
global%ybig=ybig
!> introduction of final result in an array ybig
global%zbig=zbig
!> introduction of final result in an array zbig
!We define 4 variables, full of '0', that will be necessary in the data analysis.
!allocate (z1(N*M), z2(N*M), z3(N*M), z4(N*M))
allocate (z1(N*M))
!> the variable Z1 contain the value 0
allocate (z2(N*M))
!> the variable Z2 contain the value 0
allocate (z3(N*M))
!> the variable Z3 contain the value 0
allocate (z4(N*M))
!> the variable Z4 contain the value 0
z1=0
z2=0
z3=0
z4=0
!This is the file where we write the results of the mesh creating.
write (nameprogr,*) 'pointlist.dat'
open(1,file=nameprogr)
write(1,*) N*M
write(1,*) N
write(1,*) M
!We print the result in the screen, and we write it in a file so that we can countinue the data treatment with it.
t=0
print*, 'the final result is:'
!> the finnal results are ... ,..., ..., ..., x ----,y ----,z ----
print*, '_____coordenate____x_________________y________________z_________'
do j=1,N
!> A simple do loop which shows i can take value from 1 to N
do i=1,M
!> A simple do loop which shows i can take value from 1 to M
t=t+1
print*,t
!> prints the value of t
print*, global%xbig(t)
!> prints the value of t
print*,global%ybig(t)
!> prints the value of t
print*,global%zbig(t)
!> prints the value of t
write(1,*) global%xbig(t)
write(1,*) global%ybig(t)
write(1,*) global%zbig(t)
write(1,*) z1(t)
write(1,*) z2(t)
write(1,*) z3(t)
write(1,*) z4(t)
end do
end do
close(1)
end subroutine
!> end of subroutine
end module
!>end of module
!======================================================================================================================================
!> Compile using gfortran -c module_precision.f90
!>gfortran -c module_newton.f90
!>gfortran -c module_read_file.f90
!>gfortran -c module_mesh.f90
!> gfortran final_meshgentest.f90 module_precision.o module_newton.o module_read_file.o module_mesh.o -o final_meshgentest.exe
!>./final_meshgentest.exe
!=======================================================================================================================================