/[lmdze]/trunk/Sources/filtrez/inifilr.f
ViewVC logotype

Contents of /trunk/Sources/filtrez/inifilr.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 175 - (show annotations)
Fri Feb 5 16:02:34 2016 UTC (8 years, 4 months ago) by guez
File size: 3883 byte(s)
Added argument itau_phy to ini_histins, phyetat0, phytrac and
phyredem0. Removed variable itau_phy of module temps. Avoiding side
effect in etat0 and phyetat0. The procedures ini_histins, phyetat0,
phytrac and phyredem0 are all called by physiq so there is no
cascading variable penalty.

In procedure inifilr, made the condition on colat0 weaker to allow for
rounding error.

Removed arguments flux_o, flux_g and t_slab of clmain, flux_o and
flux_g of clqh and interfsurf_hq, tslab and seaice of phyetat0 and
phyredem. NetCDF variables TSLAB and SEAICE no longer in
restartphy.nc. All these variables were related to the not-implemented
slab ocean. seaice and tslab were just set to 0 in phyetat0 and never
used nor changed. flux_o and flux_g were computed in clmain but never
used in physiq.

Removed argument swnet of clqh. Was used only to compute a local
variable, swdown, which was not used.

1 module inifilr_m
2
3 IMPLICIT NONE
4
5 INTEGER jfiltnu, jfiltnv
6 ! index of the last line filtered in northern hemisphere at rlat[uv]
7 ! latitudes
8
9 integer jfiltsu, jfiltsv
10 ! index of the first line filtered in southern hemisphere at
11 ! rlat[uv] latitudes
12
13 ! Filtre pour les champs situes sur la grille scalaire (longitudes
14 ! rlonv, latitudes rlatu) :
15 real, pointer:: matriceun(:, :, :) ! (iim, iim, jfiltnu - 1)
16 real, pointer:: matriceus(:, :, :) ! (iim, iim, jjm - jfiltsu + 1)
17
18 ! Filtre pour les champs situes sur la grille scalaire (longitudes
19 ! rlonv, latitudes rlatu), pour le filtre inverse :
20 real, pointer:: matrinvn(:, :, :) ! (iim, iim, jfiltnu - 1)
21 real, pointer:: matrinvs(:, :, :) ! (iim, iim, jjm - jfiltsu + 1)
22
23 ! Filtre pour les champs situes sur la grille de la vorticit\'e
24 ! (longitudes rlonu, latitudes rlatv)
25 real, pointer:: matricevn(:, :, :) ! (iim, iim, jfiltnv) matrice
26 real, pointer:: matricevs(:, :, :) ! (iim, iim, jjm - jfiltsv + 1)
27
28 contains
29
30 SUBROUTINE inifilr
31
32 ! From filtrez/inifilr.F, version 1.1.1.1, 2004/05/19 12:53:09
33 ! H. Upadhyaya, O. Sharma
34
35 ! This procedure computes the filtering coefficients for scalar
36 ! lines and meridional wind v lines. The modes are filtered from
37 ! modfrst to iim. We filter all those latitude lines where coefil
38 ! < 1. No filtering at poles. colat0 is to be used when alpha
39 ! (stretching coefficient) is set equal to zero for the regular
40 ! grid case.
41
42 USE dimens_m, ONLY : iim, jjm
43 USE dynetat0_m, ONLY : rlatu, rlatv, xprimu, grossismx
44 use inifgn_m, only: inifgn
45 use inifilr_hemisph_m, only: inifilr_hemisph
46 use jumble, only: new_unit
47 use nr_util, only: pi, ifirstloc, assert
48
49 ! Local:
50
51 REAL dlatu(jjm)
52 REAL rlamda(2:iim) ! > 0, in descending order
53 real eignvl(iim) ! eigenvalues (<= 0) sorted in descending order
54 INTEGER j, unit
55 REAL colat0 ! > 0
56 integer j1 ! index of negative latitude closest to the equator
57
58 real eignfnu(iim, iim), eignfnv(iim, iim)
59 ! eigenvectors of the discrete second derivative with respect to
60 ! longitude, at rlon[uv] longitudes
61
62 !-----------------------------------------------------------
63
64 print *, "Call sequence information: inifilr"
65
66 CALL inifgn(eignvl, eignfnu, eignfnv)
67
68 ! Calcul de colat0
69 forall (j = 1:jjm) dlatu(j) = rlatu(j) - rlatu(j + 1)
70 colat0 = min(0.5, minval(dlatu) / minval(xprimu(:iim)))
71 PRINT *, 'colat0 = ', colat0
72
73 rlamda = iim / pi / colat0 * grossismx / sqrt(- eignvl(2: iim))
74 print *, "1 / rlamda(iim) = ", 1. / rlamda(iim)
75 ! This is demonstrated in the notes but just to be sure:
76 call assert(rlamda(iim) * colat0 >= 1. - 2. * epsilon(0.), &
77 "inifilr rlamda(iim) * colat0")
78
79 call new_unit(unit)
80 open(unit, file = "modfrst.csv", status = "replace", action = "write")
81 write(unit, fmt = *) '"rlat (degrees)" modfrst' ! title line
82
83 j1 = ifirstloc(rlatu <= 0.)
84
85 call inifilr_hemisph(rlatu(j1 - 1:2:- 1), rlamda, unit, eignfnv, jfiltnu, &
86 matriceun, matrinvn)
87 jfiltnu = j1 - jfiltnu
88 matriceun = matriceun(:, :, jfiltnu - 1:1:- 1)
89 matrinvn = matrinvn(:, :, jfiltnu - 1:1:- 1)
90
91 call inifilr_hemisph(- rlatu(j1:jjm), rlamda, unit, eignfnv, jfiltsu, &
92 matriceus, matrinvs)
93 jfiltsu = j1 - 1 + jfiltsu
94
95 j1 = ifirstloc(rlatv <= 0.)
96
97 call inifilr_hemisph(rlatv(j1 - 1:1:- 1), rlamda, unit, eignfnu, jfiltnv, &
98 matricevn)
99 jfiltnv = j1 - jfiltnv
100 matricevn = matricevn(:, :, jfiltnv:1:- 1)
101
102 call inifilr_hemisph(- rlatv(j1:jjm), rlamda, unit, eignfnu, jfiltsv, &
103 matricevs)
104 jfiltsv = j1 - 1 + jfiltsv
105
106 close(unit)
107 PRINT *, 'jfiltnu =', jfiltnu
108 PRINT *, 'jfiltsu =', jfiltsu
109 PRINT *, 'jfiltnv =', jfiltnv
110 PRINT *, 'jfiltsv =', jfiltsv
111
112 END SUBROUTINE inifilr
113
114 end module inifilr_m

  ViewVC Help
Powered by ViewVC 1.1.21