The TELEMAC-MASCARET system  trunk
bief_close_files.f
Go to the documentation of this file.
1 ! ***************************
2  SUBROUTINE bief_close_files
3 ! ***************************
4 !
5  &(files,nfiles,pexit)
6 !
7 !***********************************************************************
8 ! BIEF V6P1 21/08/2010
9 !***********************************************************************
10 !
11 !brief
12 !
13 !history J-M HERVOUET (LNHE)
14 !+ 01/04/2009
15 !+ V6P0
16 !+
17 !
18 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
19 !+ 13/07/2010
20 !+ V6P0
21 !+ Translation of French comments within the FORTRAN sources into
22 !+ English comments
23 !
24 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
25 !+ 21/08/2010
26 !+ V6P0
27 !+ Creation of DOXYGEN tags for automated documentation and
28 !+ cross-referencing of the FORTRAN sources
29 !
30 !history Y AUDOUIN (LNHE)
31 !+ 25/05/2015
32 !+ V7P0
33 !+ Modification to comply with the hermes module
34 !
35 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
36 !| FILES |-->| ARRAY OF BIEF_FILE STRUCTURES
37 !| NFILES |-->| TOTAL NUMBER OF FILES
38 !| PEXIT |-->| LOGICAL, IF YES, P_EXIT WILL BE CALLED
39 !| | | TO STOP PARALLELISM
40 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
41 !
42  USE bief, ex_bief_close_files => bief_close_files
43 !
46 !
48  IMPLICIT NONE
49 !
50 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
51 !
52  INTEGER , INTENT(IN) :: NFILES
53  LOGICAL, INTENT(IN) :: PEXIT
54  TYPE(bief_file) , INTENT(INOUT) :: FILES(nfiles)
55 !
56 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
57 !
58  INTEGER I,IERR
59 !
60 !-----------------------------------------------------------------------
61 !
62  DO i=1,nfiles
63 !
64  IF(files(i)%NAME(1:1).NE.' ') THEN
65 !
66 ! CLOSES THE FILE
67 !
68  IF(files(i)%TYPE.EQ.'CONLIM') cycle
69  IF((files(i)%FMT(1:7).EQ.'SERAFIN')
70  & .OR.(files(i)%FMT.EQ.'MED ')) THEN
71  IF(files(i)%TYPE(1:4).EQ.'SCAL') THEN
72  IF(ipid.EQ.0.OR.files(i)%ACTION(1:4).EQ.'READ') THEN
73  CALL close_bnd(files(i)%FMT, files(i)%LU, ierr)
74  CALL check_call(ierr,'BIEF_CLOSE_FILE:CLOSE_BND')
75  CALL close_mesh(files(i)%FMT, files(i)%LU, ierr)
76  CALL check_call(ierr,'BIEF_CLOSE_FILE:CLOSE_MESH')
77  ENDIF
78  ELSE
79  CALL close_bnd(files(i)%FMT, files(i)%LU, ierr)
80  CALL check_call(ierr,'BIEF_CLOSE_FILE:CLOSE_BND')
81  CALL close_mesh(files(i)%FMT, files(i)%LU, ierr)
82  CALL check_call(ierr,'BIEF_CLOSE_FILE:CLOSE_MESH')
83  ENDIF
84  ELSE
85  CLOSE(files(i)%LU)
86  ENDIF
87 !
88  ENDIF
89 !
90  ENDDO
91 !
92 !-----------------------------------------------------------------------
93 !
94 ! PARALLEL MODE: STOPS IF PEXIT
95 !
96  IF(pexit) CALL p_exit
97 !
98 !-----------------------------------------------------------------------
99 !
100  RETURN
101  END
subroutine close_mesh(FFORMAT, FILE_ID, IERR, MESH_NUMBER)
Definition: close_mesh.f:7
subroutine p_exit
Definition: p_exit.F:4
subroutine close_bnd(FFORMAT, FILE_ID, IERR, MESH_NUMBER)
Definition: close_bnd.f:7
subroutine bief_close_files(FILES, NFILES, PEXIT)
Definition: bief.f:3