The TELEMAC-MASCARET system  trunk
prenl2.f
Go to the documentation of this file.
1 ! *****************
2  SUBROUTINE prenl2
3 ! *****************
4 !
5  &( iangnl, coefnl, ndire , nf , raisf , xlamd , xmu )
6 !
7 !***********************************************************************
8 ! TOMAWAC V6P1 22/06/2011
9 !***********************************************************************
10 !
11 !brief PREPARES THE COMPUTATION FOR THE NON-LINEAR INTERACTION
12 !+ SOURCE TERM BETWEEN QUADRUPLETS USING THE MDIA METHOD
13 !+ ("MULTIPLE DISCRETE INTERACTION APPROXIMATION")
14 !+ PROPOSED BY TOLMAN (2004)
15 !+
16 !+
17 !+ PROCEDURE SPECIFIC TO THE CASE WHERE THE FREQUENCIES
18 !+ FOLLOW A GEOMETRICAL PROGRESSION AND THE DIRECTIONS
19 !+ ARE EVENLY DISTRIBUTED OVER [0;2.PI].
20 !
21 !+note THIS SUBROUTINE IS TO BE USED IN CONJONCT
22 !+ SUBROUTINE QNLIN2, WHICH IT OPTIMISES.
23 !
24 !reference TOLMAN H.L. (2004):
25 !+ "INVERSE MODELING OF DISCRETE INTERACTION APPROXIMATIONS
26 !+ FOR NONLINEAR INTERACTIONS IN WIND WAVES". OCEAN
27 !+ MODELLING, 6, 405-422
28 !
29 !history E. GAGNAIRE-RENOU
30 !+ 04/2011
31 !+ V6P1
32 !+ CREATED
33 !
34 !history G.MATTAROLO (EDF - LNHE)
35 !+ 22/06/2011
36 !+ V6P1
37 !+ Translation of French names of the variables in argument
38 !
39 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
40 !| COEFNL |<--| COEFFICIENTS USED FOR DIA METHOD
41 !| IANGNL |<--| ANGUAR INDICES TABLE
42 !| NF |-->| NUNMBER OF FREQUENCIES
43 !| NDIRE |-->| NUMBER OF DIRECTIONS
44 !| RAISF |-->| FREQUENTIAL RATIO
45 !| XLAMD |-->| DIA STANDARD CONFIGURATION LAMBDA COEFFICIENT
46 !| XMU |-->| COEFFICIENTS FOR MDIA METHOD
47 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
48 ! !
49 ! APPELS : - PROGRAMME(S) APPELANT : WAC !
50 ! ******** - PROGRAMME(S) APPELE(S) : ANGLES, INTANG !
51 ! !
52 !
53  IMPLICIT NONE
54 !
55 !.....VARIABLES IN ARGUMENT
56 ! """""""""""""""""""""
57  INTEGER, INTENT(IN) :: NDIRE , NF
58  INTEGER, INTENT(INOUT) :: IANGNL(ndire,16)
59  DOUBLE PRECISION, INTENT(IN) :: RAISF , XLAMD , XMU
60  DOUBLE PRECISION, INTENT(INOUT) :: COEFNL(32)
61 
62 !.....LOCAL VARIABLES
63 ! """"""""""""""""""
64  INTEGER JP
65  DOUBLE PRECISION DELTA1, DELTA2, DTMOIN, DTPLUS, DTETAD, XXXX
66  DOUBLE PRECISION APLUS , AMOIN , BPLUS , BMOIN , FPLUS , FMOIN
67 !
68 !
69 !
70 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
71 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
72 ! ++++ COMPUTATION FOR K1 AND K2 WITH THE MU VALUE ++++
73 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
74 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
75  xxxx=xmu
76 !
77 !=====!---------------------------------------------------!
78 ! 1 ! COMPUTATIONS RELATED TO ANGULAR INTERPOLATION !
79 !=====!---------------------------------------------------!
80 !
81 !.....1.1 DETERMINES RESONANT DIRECTIONS
82 ! (WITH THE CONVENTION 0 < DTPLUS < DTMOIN)
83 ! """""""""""""""""""""""""""""""""""""""""""""
84  CALL angles( xxxx , dtplus, dtmoin)
85 !
86 !.....1.2 DETERMINES ANGULAR INDICES FOR THE 'STANDARD' CONFIGURATION
87 ! (CORRESPONDING TO (-DTPLUS,DTMOIN))
88 ! """"""""""""""""""""""""""""""""""""""""""""""""""""""""
89  IF (xxxx.GT.1.d-6) THEN
90  delta1=-dtplus
91  delta2= dtmoin
92  DO jp=1,ndire
93  CALL intang(iangnl(jp, 2), iangnl(jp, 1), jp , ndire , delta1)
94  CALL intang(iangnl(jp, 3), iangnl(jp, 4), jp , ndire , delta2)
95  ENDDO
96  ELSE
97  DO jp=1,ndire
98  iangnl(jp, 1)=jp
99  iangnl(jp, 2)=jp-1
100  IF (jp.EQ.1) iangnl(jp, 2)=ndire
101  iangnl(jp, 3)=jp
102  iangnl(jp, 4)=jp+1
103  IF (jp.EQ.ndire) iangnl(jp, 4)=1
104  ENDDO
105  ENDIF
106 !
107 !.....1.3 DETERMINES ANGULAR INDICES FOR THE 'IMAGE' CONFIGURATION
108 ! (CORRESPONDING TO (DTPLUS,-DTMOIN))
109 ! """""""""""""""""""""""""""""""""""""""""""""""""""""
110  IF (xxxx.GT.1.d-6) THEN
111  delta1= dtplus
112  delta2=-dtmoin
113  DO jp=1,ndire
114  CALL intang( iangnl(jp, 5), iangnl(jp, 6), jp , ndire , delta1)
115  CALL intang( iangnl(jp, 8), iangnl(jp, 7), jp , ndire , delta2)
116  ENDDO
117  ELSE
118  DO jp=1,ndire
119  iangnl(jp, 5)=jp
120  iangnl(jp, 6)=jp+1
121  IF (jp.EQ.ndire) iangnl(jp, 6)=1
122  iangnl(jp, 7)=jp
123  iangnl(jp, 8)=jp-1
124  IF (jp.EQ.1) iangnl(jp, 8)=ndire
125  ENDDO
126  ENDIF
127 !
128 !.....1.4 DETERMINES COEFFICIENTS OF ANGULAR INTERPOLATION
129 ! """""""""""""""""""""""""""""""""""""""""""
130  dtetad=360.d0/dble(ndire)
131  aplus=dtplus/dtetad-dble(int(dtplus/dtetad))
132  amoin=dtmoin/dtetad-dble(int(dtmoin/dtetad))
133 !
134 !
135 !=====!---------------------------------------------------!
136 ! 2 ! COMPUTATIONS RELATED TO FREQUENCY INTERPOLATION !
137 !=====!---------------------------------------------------!
138  fplus=log(1.d0+xxxx)/log(raisf)
139  fmoin=log(1.d0-xxxx)/log(raisf)
140  bplus=(raisf**(fplus-int(fplus) )-1.d0)/(raisf-1.d0)
141  bmoin=(raisf**(fmoin-int(fmoin)+1.d0)-1.d0)/(raisf-1.d0)
142 !
143 !
144 !=====!---------------------------------------------------!
145 ! 3 ! ASSIGNS THE COEFFICIENTS FOR QNLIN2 !
146 !=====!---------------------------------------------------!
147  coefnl( 1)=(1.d0-aplus) * (1.d0-bplus)
148  coefnl( 2)= aplus * (1.d0-bplus)
149  coefnl( 3)=(1.d0-aplus) * bplus
150  coefnl( 4)= aplus * bplus
151  coefnl( 5)=(1.d0-amoin) * (1.d0-bmoin)
152  coefnl( 6)= amoin * (1.d0-bmoin)
153  coefnl( 7)=(1.d0-amoin) * bmoin
154  coefnl( 8)= amoin * bmoin
155  coefnl( 9)=fplus
156  coefnl(10)=fmoin
157  coefnl(11)=1.d0/(1.d0+xxxx)**4
158  coefnl(12)=1.d0/(1.d0-xxxx)**4
159  coefnl(13)=dble(1)
160  coefnl(14)=dble(nf+int(1.d0-fmoin))
161 !
162 !
163 !
164 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
165 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
166 ! ++++ COMPUTATION FOR K1 AND K2 WITH THE LAMDA VALUE ++++
167 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
168 ! ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
169  xxxx=xlamd
170 !
171 !=====!---------------------------------------------------!
172 ! 1 ! COMPUTATIONS RELATED TO ANGULAR INTERPOLATION !
173 !=====!---------------------------------------------------!
174 !
175 !.....1.1 DETERMINES RESONANT DIRECTIONS
176 ! (WITH THE CONVENTION 0 < DTPLUS < DTMOIN)
177 ! """""""""""""""""""""""""""""""""""""""""""""
178  CALL angles( xxxx , dtplus, dtmoin)
179 !
180 !.....1.2 DETERMINES ANGULAR INDICES FOR THE 'STANDARD' CONFIGURATION
181 ! (CORRESPONDING TO (-DTPLUS,DTMOIN))
182 ! """"""""""""""""""""""""""""""""""""""""""""""""""""""""
183  IF (xxxx.GT.1.d-6) THEN
184  delta1=-dtplus
185  delta2= dtmoin
186  DO jp=1,ndire
187  CALL intang(iangnl(jp,10), iangnl(jp, 9), jp , ndire , delta1)
188  CALL intang(iangnl(jp,11), iangnl(jp,12), jp , ndire , delta2)
189  ENDDO
190  ELSE
191  DO jp=1,ndire
192  iangnl(jp, 9)=jp
193  iangnl(jp,10)=jp-1
194  IF (jp.EQ.1) iangnl(jp,10)=ndire
195  iangnl(jp,11)=jp
196  iangnl(jp,12)=jp+1
197  IF (jp.EQ.ndire) iangnl(jp,12)=1
198  ENDDO
199  ENDIF
200 !
201 !.....1.3 DETERMINES ANGULAR INDICES FOR THE 'IMAGE' CONFIGURATION
202 ! (CORRESPONDING TO (DTPLUS,-DTMOIN))
203 ! """""""""""""""""""""""""""""""""""""""""""""""""""""
204  IF (xxxx.GT.1.d-6) THEN
205  delta1= dtplus
206  delta2=-dtmoin
207  DO jp=1,ndire
208  CALL intang(iangnl(jp,13), iangnl(jp,14), jp , ndire , delta1)
209  CALL intang(iangnl(jp,16), iangnl(jp,15), jp , ndire , delta2)
210  ENDDO
211  ELSE
212  DO jp=1,ndire
213  iangnl(jp,13)=jp
214  iangnl(jp,14)=jp+1
215  IF (jp.EQ.ndire) iangnl(jp,14)=1
216  iangnl(jp,15)=jp
217  iangnl(jp,16)=jp-1
218  IF (jp.EQ.1) iangnl(jp,16)=ndire
219  ENDDO
220  ENDIF
221 !
222 !.....1.4 DETERMINES COEFFICIENTS OF ANGULAR INTERPOLATION
223 ! """""""""""""""""""""""""""""""""""""""""""
224  dtetad=360.d0/dble(ndire)
225  aplus=dtplus/dtetad-dble(int(dtplus/dtetad))
226  amoin=dtmoin/dtetad-dble(int(dtmoin/dtetad))
227 !
228 !
229 !=====!---------------------------------------------------!
230 ! 2 ! COMPUTATIONS RELATED TO FREQUENCY INTERPOLATION !
231 !=====!---------------------------------------------------!
232  fplus=log(1.d0+xxxx)/log(raisf)
233  fmoin=log(1.d0-xxxx)/log(raisf)
234  bplus=(raisf**(fplus-int(fplus) )-1.d0)/(raisf-1.d0)
235  bmoin=(raisf**(fmoin-int(fmoin)+1.d0)-1.d0)/(raisf-1.d0)
236 !
237 !
238 !=====!---------------------------------------------------!
239 ! 3 ! ASSIGNS THE COEFFICIENTS FOR QNLIN2 !
240 !=====!---------------------------------------------------!
241  coefnl(17)=(1.d0-aplus) * (1.d0-bplus)
242  coefnl(18)= aplus * (1.d0-bplus)
243  coefnl(19)=(1.d0-aplus) * bplus
244  coefnl(20)= aplus * bplus
245  coefnl(21)=(1.d0-amoin) * (1.d0-bmoin)
246  coefnl(22)= amoin * (1.d0-bmoin)
247  coefnl(23)=(1.d0-amoin) * bmoin
248  coefnl(24)= amoin * bmoin
249  coefnl(25)=fplus
250  coefnl(26)=fmoin
251  coefnl(27)=1.d0/(1.d0+xxxx)**4
252  coefnl(28)=1.d0/(1.d0-xxxx)**4
253  coefnl(29)=dble(1)
254  coefnl(30)=dble(nf+int(1.d0-fmoin))
255 !
256 !
257  RETURN
258  END
subroutine angles(XLAMD, DTPLUS, DTMOIN)
Definition: angles.f:7
subroutine prenl2(IANGNL, COEFNL, NDIRE, NF, RAISF, XLAMD, XMU)
Definition: prenl2.f:7
subroutine intang(LAVANT, LAPRES, IDIRE, NDIRE, DELTAD)
Definition: intang.f:7