/[lmdze]/trunk/Sources/dyn3d/Dissipation/inidissip.f
ViewVC logotype

Annotation of /trunk/Sources/dyn3d/Dissipation/inidissip.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 137 - (hide annotations)
Wed May 6 15:51:03 2015 UTC (9 years ago) by guez
File size: 3857 byte(s)
Removed unused argument missval in ma_fucoll_r[1-3]1, ma_fufill_r[1-3]1.

Split filtreg into two procedures: filtreg_scal and filtreg_v. I did
not like the test on the extent of the argument and there was no
common code between the two cases: jjm and jjm + 1. Also, it is
simpler now to just remove the argument "direct" from filtreg_v instead
of allowing it and then stopping the program if it is false.

Removed the computation of pkf in reanalyse2nat, was not used.

As a consequence of the split of filtreg, had to extract the
computation of pkf out of exner_hyb. This is clearer anyway because we
want to be able to call exner_hyb with any size in the first two
dimensions (as in test_disvert). But at the same time exner_hyb
required particular sizes for the computation of pkf. It was
awkward. The only computation of pkf is now in leapfrog.

1 guez 26 module inidissip_m
2 guez 3
3 guez 26 use dimens_m, only: llm
4 guez 3
5 guez 26 IMPLICIT NONE
6 guez 3
7 guez 26 private llm
8 guez 3
9 guez 57 REAL dtdiss ! in s
10 guez 47 integer idissip ! période de la dissipation (en pas de temps)
11 guez 65 real tetaudiv(llm), tetaurot(llm), tetah(llm) ! in s-1
12 guez 26 real cdivu, crot, cdivh
13 guez 3
14 guez 26 contains
15 guez 3
16 guez 27 SUBROUTINE inidissip
17 guez 3
18 guez 26 ! From dyn3d/inidissip.F, version 1.1.1.1 2004/05/19 12:53:06
19 guez 3
20 guez 54 ! Initialisation de la dissipation horizontale. Calcul des valeurs
21     ! propres des opérateurs par méthode itérative.
22    
23 guez 64 USE comconst, ONLY: dtvr
24     use comdissnew, only: nitergdiv, nitergrot, niterh, tetagdiv, tetagrot, &
25     tetatemp
26 guez 66 USE disvert_m, ONLY: preff, presnivs
27 guez 64 USE conf_gcm_m, ONLY: iperiod
28     USE dimens_m, ONLY: iim, jjm
29 guez 65 use divgrad2_m, only: divgrad2
30 guez 137 use filtreg_scal_m, only: filtreg_scal
31     use filtreg_v_m, only: filtreg_v
32 guez 54 use gradiv2_m, only: gradiv2
33 guez 57 use jumble, only: new_unit
34 guez 65 use nxgraro2_m, only: nxgraro2
35 guez 64 USE paramet_m, ONLY: jjp1
36 guez 3
37 guez 26 ! Variables local to the procedure:
38 guez 57 REAL zvert(llm), max_zvert ! no dimension
39     REAL, dimension(iim + 1, jjm + 1, 1):: zh, zu, gx, divgra, deltap
40     real zv(iim + 1, jjm, 1), gy(iim + 1, jjm, 1)
41 guez 40 REAL zllm
42 guez 54 INTEGER l, seed_size, ii, unit
43 guez 27 REAL tetamin ! in s
44 guez 3
45 guez 26 !-----------------------------------------------------------------------
46 guez 3
47 guez 26 PRINT *, 'Call sequence information: inidissip'
48 guez 54 call random_seed(size=seed_size)
49 guez 71 call random_seed(put=(/(1, ii = 1, seed_size)/))
50 guez 3
51 guez 54 PRINT *, 'Calcul des valeurs propres de divgrad'
52 guez 40 deltap = 1.
53 guez 54 call random_number(zh)
54     zh = zh - 0.5
55 guez 137 CALL filtreg_scal(zh, direct = .true., intensive = .true.)
56 guez 3
57 guez 26 DO l = 1, 50
58 guez 64 CALL divgrad2(1, zh, deltap, niterh, divgra, -1.)
59 guez 57 zllm = abs(maxval(divgra))
60     zh = divgra / zllm
61 guez 26 END DO
62 guez 3
63 guez 64 cdivh = 1. / zllm
64 guez 54 PRINT *, 'cdivh = ', cdivh
65 guez 3
66 guez 54 PRINT *, 'Calcul des valeurs propres de gradiv'
67     call random_number(zu)
68     zu = zu - 0.5
69 guez 137 CALL filtreg_scal(zu, direct = .true., intensive = .true.)
70 guez 54 call random_number(zv)
71     zv = zv - 0.5
72 guez 137 CALL filtreg_v(zv, intensive = .true.)
73 guez 3
74 guez 54 DO l = 1, 50
75 guez 64 CALL gradiv2(zu, zv, nitergdiv, gx, gy, -1.)
76 guez 57 zllm = max(abs(maxval(gx)), abs(maxval(gy)))
77     zu = gx / zllm
78     zv = gy / zllm
79 guez 54 end DO
80 guez 3
81 guez 64 cdivu = 1. / zllm
82 guez 54 PRINT *, 'cdivu = ', cdivu
83 guez 3
84 guez 54 PRINT *, 'Calcul des valeurs propres de nxgrarot'
85     call random_number(zu)
86     zu = zu - 0.5
87 guez 137 CALL filtreg_scal(zu, direct = .true., intensive = .true.)
88 guez 54 call random_number(zv)
89     zv = zv - 0.5
90 guez 137 CALL filtreg_v(zv, intensive = .true.)
91 guez 3
92 guez 54 DO l = 1, 50
93 guez 65 CALL nxgraro2(zu, zv, nitergrot, gx, gy, -1.)
94 guez 57 zllm = max(abs(maxval(gx)), abs(maxval(gy)))
95     zu = gx / zllm
96     zv = gy / zllm
97 guez 54 end DO
98    
99 guez 64 crot = 1. / zllm
100 guez 26 PRINT *, 'crot = ', crot
101 guez 3
102 guez 26 ! Variation verticale du coefficient de dissipation :
103 guez 27 zvert = 2. - 1. / (1. + (preff / presnivs - 1.)**2)
104     ! (between 1 and 2)
105 guez 3
106 guez 26 tetaudiv = zvert / tetagdiv
107     tetaurot = zvert / tetagrot
108     tetah = zvert / tetatemp
109 guez 54
110 guez 27 max_zvert = maxval(zvert)
111 guez 54 tetamin = min(1e6, tetagdiv / max_zvert, tetagrot / max_zvert, &
112 guez 27 tetatemp / max_zvert)
113 guez 26 PRINT *, 'tetamin = ', tetamin
114 guez 27 idissip = max(1, int(tetamin / (2 * dtvr * iperiod))) * iperiod
115 guez 26 PRINT *, 'idissip = ', idissip
116     dtdiss = idissip * dtvr
117 guez 57 PRINT *, 'dtdiss = ', dtdiss, "s"
118 guez 26
119 guez 65 call new_unit(unit)
120     open(unit, file="inidissip.csv", status="replace", action="write")
121    
122     ! Title line:
123     write(unit, fmt=*) '"presnivs (hPa)" "dtdiss * tetaudiv" ' &
124     // '"dtdiss * tetaurot" "dtdiss * tetah"'
125    
126     do l = 1, llm
127     write(unit, fmt=*) presnivs(l) / 100., dtdiss * tetaudiv(l), &
128     dtdiss * tetaurot(l), dtdiss * tetah(l)
129     end do
130     close(unit)
131     print *, 'Created file "inidissip.csv".'
132    
133 guez 26 END SUBROUTINE inidissip
134    
135     end module inidissip_m

  ViewVC Help
Powered by ViewVC 1.1.21