The TELEMAC-MASCARET system
trunk
sources
utils
bief
check_digits.f
Go to the documentation of this file.
1
! ***********************
2
SUBROUTINE
check_digits
3
! ***********************
4
!
5
&(f,t1,mesh)
6
!
7
!***********************************************************************
8
! BIEF V6P1 21/08/2010
9
!***********************************************************************
10
!
11
!brief IN PARALLEL MODE, CHECKS THAT PROCESSORS SHARING AN
12
!+ INTERFACE POINT HAVE EXACTLY THE SAME VALUE FOR ARRAY F.
13
!
14
!history J-M HERVOUET (LNHE)
15
!+ 02/06/08
16
!+ V5P9
17
!+
18
!
19
!history N.DURAND (HRW), S.E.BOURBAN (HRW)
20
!+ 13/07/2010
21
!+ V6P0
22
!+ Translation of French comments within the FORTRAN sources into
23
!+ English comments
24
!
25
!history N.DURAND (HRW), S.E.BOURBAN (HRW)
26
!+ 21/08/2010
27
!+ V6P0
28
!+ Creation of DOXYGEN tags for automated documentation and
29
!+ cross-referencing of the FORTRAN sources
30
!
31
!history J,RIEHME (ADJOINTWARE)
32
!+ November 2016
33
!+ V7P2
34
!+ Replaced EXTERNAL statements to parallel functions / subroutines
35
!+ by the INTERFACE_PARALLEL
36
!
37
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
38
!| F |-->| BIEF_OBJ STRUCTURE TO BE CHECKED
39
!| MESH |-->| MESH STRUCTURE
40
!| T1 |<->| WORK BIEF STRUCTURE, SIMILAR TO F
41
!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
42
!
43
USE
bief
44
!
45
USE
declarations_special
46
USE
interface_parallel
, ONLY
:
p_max
47
IMPLICIT NONE
48
!
49
!+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
50
!
51
TYPE
(bief_obj),
INTENT(IN )
:: F
52
TYPE
(bief_obj),
INTENT(INOUT)
:: T1
53
TYPE
(bief_mesh),
INTENT(INOUT)
:: MESH
54
!
55
!+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
56
!
57
INTEGER
I,ISTOP
58
!
59
!-----------------------------------------------------------------------
60
!
61
CALL
os
(
'X=Y '
,x=t1,y=f)
62
CALL
parcom
(t1,3,mesh)
63
istop=0
64
DO
i=1,t1%DIM1
65
IF
(t1%R(i).NE.f%R(i))
THEN
66
WRITE
(
lu
,*)
'CHECK_DIGITS : DIFFERENCE IN '
,f%NAME
67
WRITE
(
lu
,*)
' AT LOCAL POINT '
,i
68
WRITE
(
lu
,*)
' = GLOBAL POINT '
,mesh%KNOLG%I(i)
69
WRITE
(
lu
,*)
' VALUE '
,f%R(i)
70
WRITE
(
lu
,*)
' MINIMUM '
,t1%R(i)
71
WRITE
(
lu
,*)
' DIFFERENCE '
,f%R(i)-t1%R(i)
72
istop=i
73
ENDIF
74
ENDDO
75
!
76
IF
(ncsize.GT.1) istop=
p_max
(istop)
77
IF
(istop.GT.0)
THEN
78
WRITE
(
lu
,*)
'CHECK_DIGITS : ERROR ON VECTOR '
,f%NAME
79
CALL
plante(1)
80
stop
81
ENDIF
82
!
83
!-----------------------------------------------------------------------
84
!
85
RETURN
86
END
interface_parallel
Definition:
interface_parallel.f:3
declarations_special
Definition:
declarations_special.F:3
check_digits
subroutine check_digits(F, T1, MESH)
Definition:
check_digits.f:7
declarations_special::lu
integer lu
Definition:
declarations_special.F:45
interface_parallel::p_max
Definition:
interface_parallel.f:204
os
subroutine os(OP, X, Y, Z, C, IOPT, INFINI, ZERO)
Definition:
os.f:7
parcom
subroutine parcom(X, ICOM, MESH)
Definition:
parcom.f:7
bief
Definition:
bief.f:3