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

Contents of /trunk/dyn3d/Dissipation/inidissip.f

Parent Directory Parent Directory | Revision Log Revision Log


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

  ViewVC Help
Powered by ViewVC 1.1.21