The TELEMAC-MASCARET system  trunk
init_compo.f
Go to the documentation of this file.
1 ! *********************
2  SUBROUTINE init_compo
3 ! *********************
4 !
5  &(ncouches)
6 !
7 !***********************************************************************
8 ! SISYPHE V7P3
9 !***********************************************************************
10 !
11 !brief INITIAL FRACTION DISTRIBUTION, STRATIFICATION,
12 !+ VARIATION IN SPACE.
13 !
14 !history MATTHIEU GONZALES DE LINARES
15 !+ 2002
16 !+ V6P0
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-M HERVOUET (EDF LAB, LNHE)
32 !+ 2016
33 !+ V7P2
34 !+ Checking coherence of data: ZR+sediment height=ZF
35 !
36 !history R.KOPMANN (BAW)
37 !+ 30/01/2018
38 !+ V7P2
39 !+ Correct initialisation of all layers and consistency with cas-file
40 !+ by default
41 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
42 !| NCOUCHES |-->| NUMBER OF LAYER FOR EACH POINT
43 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
44 !
45  USE bief
48 !
50  IMPLICIT NONE
51 !
52 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
53 !
54 ! NPOIN
55  INTEGER, INTENT (INOUT)::NCOUCHES(*)
56 !
57 !+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
58 !
59  INTEGER I,J,K
60  DOUBLE PRECISION EPAI,HEIGHT
61 !
62 !-----------------------------------------------------------------------
63 !
64  DO j=1,npoin
65 !
66 ! BY DEFAULT : UNIFORM BED COMPOSITION
67 !
68  ncouches(j) = nomblay
69  DO k=1,nomblay
70  DO i = 1, nsicla
71  avail(j,k,i) = ava0(i)
72  ENDDO
73  END DO
74  es(j,1) = min(elay0,(zf%R(j)-zr%R(j)))
75  DO k = 2, nomblay
76  height = (zf%R(j)-zr%R(j)-elay0)
77  IF(height.GT.0.d0) THEN
78  es(j,k)=height/(nomblay-1)
79  ELSE
80  es(j,k) = 0.d0
81  ENDIF
82  ENDDO
83  ENDDO
84 !
85 !-----------------------------------------------------------------------
86 !
87  ! USER FUNCTION
88  CALL user_init_compo(ncouches)
89 !
90 !-----------------------------------------------------------------------
91 !
92 ! CHECKING THE CONSISTENCY OF DATA
93 ! THE FORMULA USED HERE ZR+SED. HEIGHT = ZF CAN BE USED TO GIVE THE
94 ! HEIGHT OF THE LAST LAYER.
95 !
96  DO j=1,mesh%NPOIN
97  epai=0.d0
98  DO i=1,ncouches(j)
99  epai=epai+es(j,i)
100  ENDDO
101  IF(abs(zr%R(j)+epai-zf%R(j)).GT.1.d-6) THEN
102  WRITE(lu,*) 'INIT_COMPO, ERROR:'
103  WRITE(lu,*) 'ZR+SEDIMENT HEIGHT=',zr%R(j)+epai
104  WRITE(lu,*) 'ZF=',zf%R(j),' ZR=',zr%R(j),
105  & ' SEDIMENT HEIGHT=',epai
106  WRITE(lu,*) 'AT POINT ',j
107  CALL plante(1)
108  stop
109  ENDIF
110  ENDDO
111 !
112 !-----------------------------------------------------------------------
113 !
114  RETURN
115  END
double precision, dimension(nsiclm) ava0
subroutine user_init_compo(NCOUCHES)
type(bief_obj), target zr
type(bief_obj), target zf
subroutine init_compo(NCOUCHES)
Definition: init_compo.f:7
double precision, dimension(:,:,:), allocatable, target avail
type(bief_mesh), target mesh
double precision, dimension(:,:), allocatable, target es
Definition: bief.f:3