The TELEMAC-MASCARET system  trunk
gretel_autop.f
Go to the documentation of this file.
1 ! ***********************
2  SUBROUTINE gretel_autop
3 ! ***********************
4  &(geo,geoformat,bnd,res,resformat,nproc,nplan_res,method)
5 !
6 !
7 !***********************************************************************
8 ! PARALLEL V6P2 21/08/2010
9 !***********************************************************************
10 !
11 !brief MERGES THE RESULTS OF A PARALLEL COMPUTATION
12 !+ TO WRITE A SINGLE FILE IN A GIVEN FORMAT.
13 !
14 !
15 !history Y. Audouin
16 !+ 02/09/2014
17 !+
18 !+ Creation of the file
19 !+ This version of gretel now handles multiple format and has a better
20 !+ memory organisation
21 !+ It also uses the hermes module for I/O
22 !
23 !
24 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
35 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
36 !
39  USE bief, ONLY: read_mesh_info
40 !
41  IMPLICIT NONE
42 !
43 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-
44 !
45  CHARACTER(LEN=PATH_LEN), INTENT(IN) :: GEO
46  CHARACTER(LEN=PATH_LEN), INTENT(IN) :: BND
47  CHARACTER(LEN=PATH_LEN), INTENT(IN) :: RES
48  CHARACTER(LEN=8), INTENT(INOUT) :: GEOFORMAT,RESFORMAT
49  INTEGER, INTENT(IN) :: NPROC
50  INTEGER, INTENT(INOUT) :: NPLAN_RES
51  INTEGER, INTENT(IN) :: METHOD
52 !
53 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-
54 !
55  INTEGER IPID
56  INTEGER I,J,IELEM
57  INTEGER NPLAN_GEO,NELEM_GEO,NDP,NELEBD, NPTFR, NPTIR
58  INTEGER :: NDIM, X_ORIG, Y_ORIG
59 !
60  INTEGER, DIMENSION(:) , ALLOCATABLE :: IPOBO_GEO,IPOBO3D
61  INTEGER, DIMENSION(:), ALLOCATABLE :: KNOLG, TMP2
62  INTEGER, DIMENSION(:), ALLOCATABLE :: IKLE_GEO,IKLE3D
63  INTEGER, DIMENSION(:), ALLOCATABLE :: IKLE_BND
64 !
65  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: TMP, X, Y
66 !
67  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: X3D, Y3D, Z3D
68 !
69  CHARACTER(LEN=300) :: RESPAR
70 !
71  CHARACTER(LEN=80) TITSEL
72  CHARACTER(LEN=32),ALLOCATABLE :: TEXTELU(:)
73  CHARACTER(LEN=16),ALLOCATABLE :: VAR_NAME(:), VAR_UNIT(:)
74  CHARACTER(LEN=16) :: VARNAME
75  CHARACTER(LEN=11) EXTENS
76  EXTERNAL extens
77  INTRINSIC real
78 !
79  INTEGER IERR, NRES, NRESPAR, NGEO
80  INTEGER TYP_ELEM, TYP_BND_ELEM
81  INTEGER DATE(3), TIME(3)
82  INTEGER NTIMESTEP_RES
83  INTEGER NPOIN_GEO, NPOIN_RES, NPOIN_PAR
84  INTEGER NVAR_RES,NVAR_GEO
85  INTEGER NPOIN3D, NELEM3D
86  INTEGER DATE_TMP(6)
87 !
88 !-------------------------------------------------------------------------
89 !
90 !
91 !|==================================================================|
92 !| |
93 !| START: MERGES FILES RESULTING FROM THE DOMAIN DECOMPOSITION |
94 !| |
95 !|==================================================================|
96 !
97 ! READS FILE NAMES AND THE NUMBER OF PROCESSORS / PARTITIONS
98 !
99 !
100 !
101 ! Header information
102 !
103  respar = trim(res) // extens(nproc-1,0)
104  CALL open_mesh(resformat,respar,nrespar,'READ ',ierr)
105  CALL check_call(ierr,"GRETEL:OPEN_MESH:RESPAR")
106 ! Opening result file after so that it will be the same endianess as
107 ! the partitionned result files
108  CALL open_mesh(resformat,res,nres,'WRITE ',ierr)
109  CALL check_call(ierr,"GRETEL:OPEN_MESH:RES")
110 !
111  ! GET THE MESH TITLE
112  CALL get_mesh_title(resformat,nrespar,titsel,ierr)
113  CALL check_call(ierr,"GRETEL:GET_MESH_TITLE")
114 
115 ! Get the number of variable
116  CALL get_data_nvar(resformat,nrespar,nvar_res,ierr)
117  CALL check_call(ierr,"GRETEL:GET_DATA_NVAR")
118 !
119  ALLOCATE(textelu(nvar_res),stat=ierr)
120  CALL check_allocate(ierr,'GRETEL:TEXTELU')
121  ALLOCATE(var_name(nvar_res),stat=ierr)
122  CALL check_allocate(ierr,'GRETEL:VAR_NAME')
123  ALLOCATE(var_unit(nvar_res),stat=ierr)
124  CALL check_allocate(ierr,'GRETEL:VAR_UNIT')
125 !
126  CALL get_data_var_list(resformat,nrespar,nvar_res,var_name,
127  & var_unit,ierr)
128  CALL check_call(ierr,"GRETEL:GET_DATA_VAR_LIST")
129 !
130  WRITE(lu,*) 'TITLE=',titsel
131  WRITE(lu,*) 'NBVAR=',nvar_res
132  DO i=1,nvar_res
133  textelu(i)(1:16) = var_name(i)
134  textelu(i)(17:32) = var_unit(i)
135  WRITE(lu,*) 'VARIABLE ',i,' : ',textelu(i)
136  ENDDO ! I
137 !
138  DEALLOCATE(var_name)
139  DEALLOCATE(var_unit)
140 !
141 ! WE NEED TO GET THE NUMBER OF PLANES IN THE PARTITIONNED FILE
142 ! TO KNOW IF WE NEED TO TRANFORM THE GEOMETRY IN 3D GEOMETRY
143  CALL get_mesh_nplan(resformat,nrespar,nplan_res,ierr)
144  CALL check_call(ierr,"GRETEL:MESH_NPLAN")
145 !
146 ! Get the number of timestep
147  CALL get_data_ntimestep(resformat,nrespar,ntimestep_res,ierr)
148  CALL check_call(ierr,"GRETEL:GET_DATA_NTIMESTEP")
149 
150  CALL close_mesh(resformat,nrespar,ierr)
151  CALL check_call(ierr,"GRETEL:CLOSE_MESH:RESPAR")
152 
153  CALL set_header(resformat,nres,titsel,nvar_res,textelu,ierr)
154 !
155 ! Geometry information
156 !
157  CALL open_mesh(geoformat,geo,ngeo,'READ ',ierr)
158  CALL check_call(ierr,"GRETEL:OPEN_MESH:GEO")
159 !
160 
161 ! Boundary file
162  CALL open_bnd(geoformat,bnd,ngeo,'READ ',ierr)
163  CALL check_call(ierr,"GRETEL:OPEN_BND:GEO")
164 
165  CALL read_mesh_info(geoformat,ngeo,titsel,nvar_geo,npoin_geo,
166  & typ_elem,nelem_geo,nptfr,nptir,ndp,nplan_geo,
167  & x_orig,y_orig,typ_bnd_elem,nelebd)
168 !
169  WRITE(lu,*) 'GEO MESH INFORMATIONS:'
170  WRITE(lu,*) 'NELEM=',nelem_geo
171  WRITE(lu,*) 'NPOIN=',npoin_geo
172  WRITE(lu,*) 'NDP=',ndp
173  WRITE(lu,*) 'TYP_ELEM=',typ_elem
174 !
175  ALLOCATE(ikle_geo(nelem_geo*ndp),stat=ierr)
176  CALL check_allocate(ierr,'GRETEL:IKLE_GEO')
177  ALLOCATE(ipobo_geo(npoin_geo),stat=ierr)
178  CALL check_allocate(ierr,'GRETEL:IPOBO')
179 !
180  CALL read_mesh_conn(geoformat,ngeo,npoin_geo,typ_elem,nelem_geo,
181  & ndp,typ_bnd_elem,nelebd,ikle_geo, ipobo_geo)
182 
183  IF(nplan_res.LE.1) THEN
184  ndim = 2
185  ELSE
186  ndim = 3
187  ENDIF
188  ! GET 2D COORDINATES
189  ALLOCATE(x(npoin_geo),stat=ierr)
190  CALL check_allocate(ierr,'GRETEL:X')
191  ALLOCATE(y(npoin_geo),stat=ierr)
192  CALL check_allocate(ierr,'GRETEL:Y')
193  ALLOCATE(z3d(npoin_geo*nplan_res),stat=ierr)
194  CALL check_allocate(ierr,'GRETEL:Z3D')
195  ! GET MESH COORDINATES FROM THE GEO MESH
196  CALL get_mesh_coord(geoformat,ngeo,1,2,npoin_geo,x,ierr)
197  CALL check_call(ierr,'GRETEL:GET_MESH_COORD:X:GEO')
198  CALL get_mesh_coord(geoformat,ngeo,2,2,npoin_geo,y,ierr)
199  CALL check_call(ierr,'GRETEL:GET_MESH_COORD:Y:GEO')
200  !
201  ! Update coordiantes with coordinates from the partitionned files
202  ! as they could have been modified by corrxy
203  DO ipid = 0, nproc-1
204 !
205  respar = trim(res) // extens(nproc-1,ipid)
206  CALL open_mesh(resformat,respar,nrespar,'READ ',ierr)
207  CALL check_call(ierr,"GRETEL:OPEN_MESH:RESPAR2")
208 !
209  CALL get_mesh_npoin(resformat,nrespar,typ_elem,npoin_par,ierr)
210  CALL check_call(ierr,"GRETEL:GET_MESH_NPOIN:RESPAR")
211 !
212  ALLOCATE(knolg(npoin_par),stat=ierr)
213  CALL check_allocate(ierr,'GRETEL:KNOLG')
214  ALLOCATE(tmp(npoin_par),stat=ierr)
215  CALL check_allocate(ierr,'GRETEL:TMP')
216 !
217  CALL get_mesh_l2g_numbering(resformat,nrespar,knolg,
218  & npoin_par,ierr)
219  CALL check_call(ierr,'GRETEL:GET_MESH_L2G_NUMBERING:RESPAR')
220 !
221  CALL get_mesh_coord(resformat,nrespar,1,ndim,npoin_par,tmp,ierr)
222  CALL check_call(ierr,'GRETEL:GET_MESH_COORD:X:RESPAR')
223  DO i=1,npoin_par/(max(nplan_res,1))
224  x(knolg(i)) = tmp(i)
225  ENDDO
226  CALL get_mesh_coord(resformat,nrespar,2,ndim,npoin_par,tmp,ierr)
227  CALL check_call(ierr,'GRETEL:GET_MESH_COORD:Y:RESPAR')
228  DO i=1,npoin_par/(max(nplan_res,1))
229  y(knolg(i)) = tmp(i)
230  ENDDO
231  ! If 3d getting Z from result file (First variable at time=0.0)
232  IF(ndim.EQ.3) THEN
233  varname = textelu(1)(1:16)
234  CALL get_data_value(resformat,nrespar,0,varname,tmp,
235  & npoin_par,ierr)
236  DO i=1,npoin_par
237  z3d(knolg(i)) = tmp(i)
238  ENDDO
239  ENDIF
240  ! Getting the date from result file
241  CALL get_mesh_date(resformat,nrespar,date_tmp,ierr)
242  CALL check_call(ierr,'GRETEL:GET_MESH_DATE;RESPAR')
243  DO i=1,3
244  date(i) = date_tmp(i)
245  time(i) = date_tmp(i+3)
246  ENDDO
247  !
248  CALL close_mesh(resformat,nrespar,ierr)
249  CALL check_call(ierr,'GRETEL:CLOSEMESH:RESPAR')
250  DEALLOCATE(tmp)
251  DEALLOCATE(knolg)
252  ENDDO ! IPID
253  !
254  ! IF WE HAVE A 3D RESULT WE NEED TO TRANSFORM THE MESH IN 3D
255  ! WRITES THE MESH INFORMATION TO THE MERGED FILE
256  WRITE(lu,*) 'WRITING MESH'
257  IF(ndim.EQ.2) THEN
258  ! 2D
259  ALLOCATE(tmp2(nelem_geo*ndp),stat=ierr)
260  CALL check_allocate(ierr,'GRETEL:TMP0')
261  DO i = 1,ndp
262  DO ielem = 1,nelem_geo
263  tmp2((i-1)*nelem_geo + ielem) = ikle_geo((ielem-1)*ndp+i)
264  ENDDO
265  ENDDO
266 
267  CALL set_mesh(resformat,nres,2,typ_elem,ndp,nptfr,nptir,
268  & nelem_geo,npoin_geo,tmp2,ipobo_geo,ipobo_geo,x,y,
269  & nplan_res,date,time,x_orig,y_orig,ierr,
270  & in_place=.true.)
271  CALL check_call(ierr,'GRETEL:SET_MESH:RES')
272  DEALLOCATE(ikle_geo)
273  DEALLOCATE(tmp2)
274  DEALLOCATE(ipobo_geo)
275  DEALLOCATE(x)
276  DEALLOCATE(y)
277  npoin_res = npoin_geo
278  ELSE
279  ! 3D
280  ndp = 6
281  typ_elem = prism_elt_type
282  npoin3d = npoin_geo * nplan_res
283  nelem3d = nelem_geo * (nplan_res-1)
284  nptfr = 0
285  nptir = 0
286  npoin_res = npoin3d
287  ALLOCATE(ikle3d(nelem3d*ndp),stat=ierr)
288  CALL check_allocate(ierr, 'GRETEL:IKLE3D')
289  ALLOCATE(ipobo3d(npoin3d),stat=ierr)
290  CALL check_allocate(ierr, 'GRETEL:IPOBO3D')
291 !
292  ! BUILDING 3D IKLE
293  DO i=1,nplan_res-1
294  DO j=1,nelem_geo
295  ikle3d(j+(i-1)*nelem_geo + (0*nelem3d)) =
296  & ikle_geo((j-1)*3+1) + (i-1)*npoin_geo
297  ikle3d(j+(i-1)*nelem_geo + (1*nelem3d)) =
298  & ikle_geo((j-1)*3+2) + (i-1)*npoin_geo
299  ikle3d(j+(i-1)*nelem_geo + (2*nelem3d)) =
300  & ikle_geo((j-1)*3+3) + (i-1)*npoin_geo
301  ikle3d(j+(i-1)*nelem_geo + (3*nelem3d)) =
302  & ikle_geo((j-1)*3+1) + (i)*npoin_geo
303  ikle3d(j+(i-1)*nelem_geo + (4*nelem3d)) =
304  & ikle_geo((j-1)*3+2) + (i)*npoin_geo
305  ikle3d(j+(i-1)*nelem_geo + (5*nelem3d)) =
306  & ikle_geo((j-1)*3+3) + (i)*npoin_geo
307  ENDDO
308  ENDDO
309  ! DEFAULT IPOBO
310  DO i=1,npoin3d
311  ipobo3d(i) = 0
312  ENDDO
313  ! WE DONT NEED THEM ANYMORE
314  DEALLOCATE(ikle_geo)
315  DEALLOCATE(ipobo_geo)
316  ! BUILD THE COORDINATES FROM THE 2D COORDINATES
317  ALLOCATE(x3d(npoin_geo*nplan_res),stat=ierr)
318  CALL check_allocate(ierr,'GRETEL:X3D')
319  ALLOCATE(y3d(npoin_geo*nplan_res),stat=ierr)
320  CALL check_allocate(ierr,'GRETEL:Y3D')
321  !
322  DO i=1,npoin_geo
323  DO j=1,nplan_res
324  x3d(i+(j-1)*npoin_geo) = x(i)
325  y3d(i+(j-1)*npoin_geo) = y(i)
326  ENDDO
327  ENDDO
328  DEALLOCATE(x)
329  DEALLOCATE(y)
330  date = (/0,0,0/)
331  time = (/0,0,0/)
332  CALL set_mesh(resformat,nres,3,typ_elem,ndp,nptfr,nptir,nelem3d,
333  & npoin3d,ikle3d,ipobo3d,ipobo3d,x3d,y3d,
334  & nplan_res,date,time,x_orig,y_orig,ierr,
335  & z=z3d,in_place=.true.)
336  CALL check_call(ierr,'GRETEL:SET_MESH:RES')
337  DEALLOCATE(ikle3d)
338  DEALLOCATE(ipobo3d)
339  DEALLOCATE(x3d)
340  DEALLOCATE(y3d)
341  DEALLOCATE(z3d)
342 
343 
344  ENDIF
345  ! Transfering boundary information
346  ! Getting boundary connectivity
347  IF(geoformat.EQ.resformat) THEN
348  ALLOCATE(ikle_bnd(nelebd*2), stat=ierr)
349  CALL get_bnd_connectivity(geoformat, ngeo, typ_bnd_elem, nelebd,
350  & 2, ikle_bnd, ierr)
351  CALL check_call(ierr,'GRETEL:GET_BND_CONNECTIVITY:GEO')
352 
353  CALL transfer_group_info(geoformat, ngeo, nres, typ_elem,
354  & typ_bnd_elem,ikle_bnd,nelebd,2,.true.,.true.,ierr)
355  CALL check_call(ierr,'GRETEL:TRANSFER_GROUP_INFO:GEO')
356  DEALLOCATE(ikle_bnd)
357  ENDIF
358 !
359 ! Read results informations from partitioned files
360 !
361  CALL merge_data
362  &(npoin_res, nvar_res, ntimestep_res, nproc, resformat, nres,
363  & typ_elem, textelu, res, ndim, nplan_res, npoin_geo, method)
364 
365  ! DONE
366  CALL close_mesh(resformat,nres,ierr)
367  CALL check_call(ierr,'GRETEL:CLOSEMESH:RES')
368  CALL close_bnd(geoformat,ngeo,ierr)
369  CALL check_call(ierr,'GRETEL:CLOSE_BND:GEO')
370  CALL close_mesh(geoformat,ngeo,ierr)
371  CALL check_call(ierr,'GRETEL:CLOSE_MESH:GEO')
372 
373  DEALLOCATE(textelu)
374  WRITE(lu,*) 'END OF PROGRAM, ',ntimestep_res,' DATASETS FOUND'
375 
376  END SUBROUTINE gretel_autop
subroutine get_mesh_npoin(FFORMAT, FID, TYP_ELEM, NPOIN, IERR)
Definition: get_mesh_npoin.f:7
subroutine transfer_group_info(FFORMAT, FID, FID2, TYPE_ELT, TYPE_BND_ELT, IKLE_BND, NELEBD, NDP, TRANS_ELEM, TRANS_POINT, IERR)
integer, parameter prism_elt_type
subroutine close_mesh(FFORMAT, FILE_ID, IERR, MESH_NUMBER)
Definition: close_mesh.f:7
subroutine get_bnd_connectivity(FFORMAT, FID, TYP_BND_ELEM, NELEBD, NDP, IKLE_BND, IERR)
subroutine set_mesh(FFORMAT, FILE_ID, MESH_DIM, TYPELM, NDP, NPTFR, NPTIR, NELEM, NPOIN, IKLE, IPOBO, KNOLG, X, Y, NPLAN, DATE, TIME, X_ORIG, Y_ORIG, IERR, Z, IN_PLACE)
Definition: set_mesh.f:9
subroutine get_data_nvar(FFORMAT, FID, NVAR, IERR)
Definition: get_data_nvar.f:7
subroutine get_data_var_list(FFORMAT, FID, NVAR, VARLIST, UNITLIST, IERR)
subroutine gretel_autop(GEO, GEOFORMAT, BND, RES, RESFORMAT, NPROC, NPLAN_RES, METHOD)
Definition: gretel_autop.f:6
subroutine close_bnd(FFORMAT, FILE_ID, IERR, MESH_NUMBER)
Definition: close_bnd.f:7
subroutine get_data_value(FFORMAT, FID, RECORD, VAR_NAME, RES_VALUE, N, IERR)
Definition: get_data_value.f:7
subroutine read_mesh_info(FFORMAT, NFIC, TITLE, NVAR, NPOIN, TYP_ELEM, NELEM, NPTFR, NPTIR, NDP, NPLAN, X_ORIG, Y_ORIG, TYP_BND_ELEM, NELEBD)
Definition: read_mesh_info.f:8
subroutine get_mesh_title(FFORMAT, FID, TITLE, IERR)
Definition: get_mesh_title.f:7
subroutine get_mesh_date(FFORMAT, FID, DATE, IERR)
Definition: get_mesh_date.f:7
subroutine get_mesh_nplan(FFORMAT, FID, NPLAN, IERR)
Definition: get_mesh_nplan.f:7
subroutine set_header(FFORMAT, FILE_ID, TITLE, NVAR, VAR_NAME, IERR)
Definition: set_header.f:7
subroutine get_mesh_coord(FFORMAT, FID, JDIM, NDIM, NPOIN, COORD, IERR)
Definition: get_mesh_coord.f:7
subroutine read_mesh_conn(FFORMAT, NFIC, NPOIN, TYP_ELEM, NELEM, NDP, TYP_BND_ELEM, NELEBD, IKLE, IPOBO)
Definition: read_mesh_conn.f:8
subroutine open_mesh(FFORMAT, FILE_NAME, FILE_ID, OPENMODE, IERR, MESH_NUMBER)
Definition: open_mesh.f:7
subroutine open_bnd(FFORMAT, FILE_NAME, FILE_ID, OPENMODE, IERR, MESH_NUMBER)
Definition: open_bnd.f:7
subroutine get_mesh_l2g_numbering(FFORMAT, FID, KNOLG, NPOIN, IERR)
subroutine get_data_ntimestep(FFORMAT, FID, NTIMESTEP, IERR)
subroutine merge_data(NPOIN_RES, NVAR_RES, NTIMESTEP_RES, NPROC, RESFORMAT, NRES, TYP_ELEM, TEXTELU, RES, NDIM, NPLAN_RES, NPOIN_GEO, METHOD)
Definition: merge_data.f:7
Definition: bief.f:3