The TELEMAC-MASCARET system  trunk
prenl1.f
Go to the documentation of this file.
1 ! *****************
2  SUBROUTINE prenl1
3 ! *****************
4 !
5  &( iangnl, coefnl, ndire , nf , raisf , xlamd )
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 DIA METHOD
13 !+ ("DISCRETE INTERACTION APPROXIMATION") PROPOSED BY
14 !+ HASSELMANN AND HASSELMANN (1985).
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 CONJONCTION WITH THE
22 !+ SUBROUTINE QNLIN1, WHICH IT OPTIMISES.
23 !
24 !reference HASSELMANN S., HASSELMANN K. ET AL.(1985) :
25 !+ "COMPUTATIONS AND PARAMETERIZATIONS OF THE NONLINEAR
26 !+ ENERGY TRANSFER IN GRAVITY-WAVE SPECTRUM. PART1 :
27 !+ A NEW METHOD FOR EFFICIENT COMPUTATION OF THE EXACT
28 !+ NON-LINEAR TRANSFER INTEGRAL". JPO, VOL 15, PP 1369-1377.
29 !reference HASSELMANN S., HASSELMANN K. ET AL.(1985) :
30 !+ "COMPUTATIONS AND PARAMETERIZATIONS OF THE NONLINEAR
31 !+ ENERGY TRANSFER IN GRAVITY-WAVE SPECTRUM. PART2 :
32 !+ PARAMETERIZATIONS OF THE NONLINEAR ENERGY TRANSFER
33 !+ FOR APPLICATION IN WAVE MODELS". JPO, VOL 15, PP 1378-1391.
34 !
35 !history M. BENOIT
36 !+ 26/06/96
37 !+ V1P2
38 !+ CREATED
39 !
40 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
41 !+ 13/07/2010
42 !+ V6P0
43 !+ Translation of French comments within the FORTRAN sources into
44 !+ English comments
45 !
46 !history N.DURAND (HRW), S.E.BOURBAN (HRW)
47 !+ 21/08/2010
48 !+ V6P0
49 !+ Creation of DOXYGEN tags for automated documentation and
50 !+ cross-referencing of the FORTRAN sources
51 !
52 !history G.MATTAROLO (EDF - LNHE)
53 !+ 22/06/2011
54 !+ V6P1
55 !+ Translation of French names of the variables in argument
56 !
57 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
58 !| COEFNL |<--| COEFFICIENTS USED FOR DIA METHOD
59 !| IANGNL |<--| ANGULAR INDICES TABLE
60 !| NF |-->| NUNMBER OF FREQUENCIES
61 !| NDIRE |-->| NUMBER OF DIRECTIONS
62 !| RAISF |-->| FREQUENTIAL RATIO
63 !| XLAMD |-->| DIA STANDARD CONFIGURATION LAMBDA COEFFICIENT
64 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
65 !
66  USE interface_tomawac, ex_prenl1 => prenl1
67  IMPLICIT NONE
68 !
69 !.....VARIABLES IN ARGUMENT
70 ! """""""""""""""""""""
71  INTEGER, INTENT(IN) :: NDIRE , NF
72  INTEGER, INTENT(INOUT) :: IANGNL(ndire,8)
73  DOUBLE PRECISION, INTENT(IN) :: RAISF , XLAMD
74  DOUBLE PRECISION, INTENT(INOUT) :: COEFNL(16)
75 !
76 !.....LOCAL VARIABLES
77 ! """"""""""""""""""
78  INTEGER JP
79  DOUBLE PRECISION DELTA1, DELTA2, DTMOIN, DTPLUS, DTETAD
80  DOUBLE PRECISION APLUS , AMOIN , BPLUS , BMOIN , FPLUS , FMOIN
81 !
82 !=====C---------------------------------------------------C
83 ! 1 C COMPUTATIONS RELATED TO ANGULAR INTERPOLATION C
84 !=====C---------------------------------------------------C
85 !
86 !.....1.1 DETERMINES RESONANT DIRECTIONS
87 ! (WITH THE CONVENTION 0
88 ! """""""""""""""""""""""""""""""""""""""""""""
89  CALL angles( xlamd , dtplus, dtmoin)
90 !
91 !.....1.2 DETERMINES ANGULAR INDICES FOR THE 'STANDARD' CONFIGURATION
92 ! (CORRESPONDING TO (-DTPLUS,DTMOIN))
93 ! """"""""""""""""""""""""""""""""""""""""""""""""""""""""
94  delta1=-dtplus
95  delta2= dtmoin
96  DO jp=1,ndire
97  CALL intang( iangnl(jp,2) , iangnl(jp,1) , jp , ndire , delta1)
98  CALL intang( iangnl(jp,3) , iangnl(jp,4) , jp , ndire , delta2)
99  ENDDO ! JP
100 !
101 !.....1.3 DETERMINES ANGULAR INDICES FOR THE 'IMAGE' CONFIGURATION
102 ! (CORRESPONDING TO (DTPLUS,-DTMOIN))
103 ! """""""""""""""""""""""""""""""""""""""""""""""""""""
104  delta1= dtplus
105  delta2=-dtmoin
106  DO jp=1,ndire
107  CALL intang( iangnl(jp,5) , iangnl(jp,6) , jp , ndire , delta1)
108  CALL intang( iangnl(jp,8) , iangnl(jp,7) , jp , ndire , delta2)
109  ENDDO ! JP
110 !
111 !.....1.4 DETERMINES COEFFICIENTS OF ANGULAR INTERPOLATION
112 ! """""""""""""""""""""""""""""""""""""""""""
113  dtetad=360.d0/dble(ndire)
114  aplus=dtplus/dtetad-dble(int(dtplus/dtetad))
115  amoin=dtmoin/dtetad-dble(int(dtmoin/dtetad))
116 !
117 !
118 !=====C---------------------------------------------------C
119 ! 2 C COMPUTATIONS RELATED TO FREQUENCY INTERPOLATION C
120 !=====C---------------------------------------------------C
121  fplus=log(1.d0+xlamd)/log(raisf)
122  fmoin=log(1.d0-xlamd)/log(raisf)
123  bplus=(raisf**(fplus-int(fplus) )-1.d0)/(raisf-1.d0)
124  bmoin=(raisf**(fmoin-int(fmoin)+1.d0)-1.d0)/(raisf-1.d0)
125 !
126 !
127 !=====C---------------------------------------------------C
128 ! 3 C ASSIGNS THE COEFFICIENTS FOR QNLIN1 C
129 !=====C---------------------------------------------------C
130  coefnl( 1)=(1.d0-aplus) * (1.d0-bplus)
131  coefnl( 2)= aplus * (1.d0-bplus)
132  coefnl( 3)=(1.d0-aplus) * bplus
133  coefnl( 4)= aplus * bplus
134  coefnl( 5)=(1.d0-amoin) * (1.d0-bmoin)
135  coefnl( 6)= amoin * (1.d0-bmoin)
136  coefnl( 7)=(1.d0-amoin) * bmoin
137  coefnl( 8)= amoin * bmoin
138  coefnl( 9)=fplus
139  coefnl(10)=fmoin
140  coefnl(11)=1.d0/(1.d0+xlamd)**4
141  coefnl(12)=1.d0/(1.d0-xlamd)**4
142  coefnl(13)=dble(1)
143  coefnl(14)=dble(nf+int(1.d0-fmoin))
144 !
145  RETURN
146  END
subroutine prenl1(IANGNL, COEFNL, NDIRE, NF, RAISF, XLAMD)
Definition: prenl1.f:7
subroutine angles(XLAMD, DTPLUS, DTMOIN)
Definition: angles.f:7
subroutine intang(LAVANT, LAPRES, IDIRE, NDIRE, DELTAD)
Definition: intang.f:7