LMDZ
setup_trans.F90
Go to the documentation of this file.
1 SUBROUTINE setup_trans(KSMAX,KDGL,KLOEN,LDLINEAR_GRID,LDSPLIT,&
2 &kapsets,ktmax,kresol)
3 
4 !**** *SETUP_TRANS* - Setup transform package for specific resolution
5 
6 ! Purpose.
7 ! --------
8 ! To setup for making spectral transforms. Each call to this routine
9 ! creates a new resolution up to a maximum of NMAX_RESOL set up in
10 ! SETUP_TRANS0. You need to call SETUP_TRANS0 before this routine can
11 ! be called.
12 
13 !** Interface.
14 ! ----------
15 ! CALL SETUP_TRANS(...)
16 
17 ! Explicit arguments : KLOEN,LDLINEAR_GRID,LDSPLIT,KAPSETS are optional arguments
18 ! --------------------
19 ! KSMAX - spectral truncation required
20 ! KDGL - number of Gaussian latitudes
21 ! KLOEN(:) - number of points on each Gaussian latitude [2*KDGL]
22 ! LDSPLIT - true if split latitudes in grid-point space [false]
23 ! LDLINEAR_GRID - true if linear grid
24 ! KAPSETS - Number of apple sets in the distribution [0]
25 ! KTMAX - truncation order for tendencies?
26 ! KRESOL - the resolution identifier
27 
28 ! KSMAX,KDGL,KTMAX and KLOEN are GLOBAL variables desribing the resolution
29 ! in spectral and grid-point space
30 
31 ! LDSPLIT and KAPSETS describe the distribution among processors of
32 ! grid-point data and has no relevance if you are using a single processor
33 
34 ! Method.
35 ! -------
36 
37 ! Externals. SET_RESOL - set resolution
38 ! ---------- SETUP_DIMS - setup distribution independent dimensions
39 ! SUMP_TRANS_PRELEG - first part of setup of distr. environment
40 ! SULEG - Compute Legandre polonomial and Gaussian
41 ! Latitudes and Weights
42 ! SETUP_GEOM - Compute arrays related to grid-point geometry
43 ! SUMP_TRANS - Second part of setup of distributed environment
44 ! SUFFT - setup for FFT
45 
46 ! Author.
47 ! -------
48 ! Mats Hamrud *ECMWF*
49 
50 ! Modifications.
51 ! --------------
52 ! Original : 00-03-03
53 
54 ! ------------------------------------------------------------------
55 
56 USE parkind1 ,ONLY : jpim ,jprb
57 
58 !ifndef INTERFACE
59 
60 USE tpm_gen
61 USE tpm_dim
62 USE tpm_distr
63 USE tpm_geometry
64 USE tpm_fields
65 USE tpm_fft
66 
67 USE set_resol_mod
71 USE suleg_mod
73 USE sufft_mod
75 USE yomhook ,ONLY : lhook, dr_hook
76 
77 !endif INTERFACE
78 
79 IMPLICIT NONE
80 
81 ! Dummy arguments
82 
83 INTEGER(KIND=JPIM) ,INTENT(IN) :: KSMAX,KDGL
84 INTEGER(KIND=JPIM) ,OPTIONAL,INTENT(IN) :: KLOEN(:)
85 LOGICAL ,OPTIONAL,INTENT(IN) :: LDLINEAR_GRID
86 LOGICAL ,OPTIONAL,INTENT(IN) :: LDSPLIT
87 INTEGER(KIND=JPIM) ,OPTIONAL,INTENT(IN) :: KAPSETS
88 INTEGER(KIND=JPIM) ,OPTIONAL,INTENT(IN) :: KTMAX
89 INTEGER(KIND=JPIM) ,OPTIONAL,INTENT(OUT):: KRESOL
90 
91 !ifndef INTERFACE
92 
93 ! Local variables
94 INTEGER(KIND=JPIM) :: JGL
95 
96 LOGICAL :: LLP1,LLP2
97 REAL(KIND=JPRB) :: ZHOOK_HANDLE
98 
99 ! ------------------------------------------------------------------
100 
101 IF (lhook) CALL dr_hook('SETUP_TRANS',0,zhook_handle)
102 
103 IF(msetup0 /= 1) THEN
104  CALL abort_trans('SETUP_TRANS: SETUP_TRANS0 HAS TO BE CALLED BEFORE SETUP_TRANS')
105 ENDIF
106 llp1 = nprintlev>0
107 llp2 = nprintlev>1
108 IF(llp1) WRITE(nout,*) '=== ENTER ROUTINE SETUP_TRANS ==='
109 
110 ! Allocate resolution dependent structures
111 IF(.NOT. ALLOCATED(dim_resol)) THEN
112  ndef_resol = 1
113  ALLOCATE(dim_resol(nmax_resol))
114  ALLOCATE(fields_resol(nmax_resol))
115  ALLOCATE(geom_resol(nmax_resol))
116  ALLOCATE(distr_resol(nmax_resol))
117  ALLOCATE(fft_resol(nmax_resol))
118 ELSE
120  IF(ndef_resol > nmax_resol) THEN
121  CALL abort_trans('SETUP_TRANS:NDEF_RESOL > NMAX_RESOL')
122  ENDIF
123 ENDIF
124 
125 IF (PRESENT(kresol)) THEN
126  kresol=ndef_resol
127 ENDIF
128 
129 ! Point at structures due to be initialized
130 CALL set_resol(ndef_resol)
131 
132 IF(llp1) WRITE(nout,*) '=== DEFINING RESOLUTION ',ncur_resol
133 
134 
135 
136 ! Defaults for optional arguments
137 
138 
139 g%LREDUCED_GRID = .false.
140 g%LINEAR_GRID = .false.
141 d%LSPLIT = .false.
142 d%NAPSETS = 0
143 
144 ! NON-OPTIONAL ARGUMENTS
145 r%NSMAX = ksmax
146 r%NDGL = kdgl
147 r%NDLON = 2*kdgl
148 
149 IF (kdgl <= 0 .OR. mod(kdgl,2) /= 0) THEN
150  CALL abort_trans ('SETUP_TRANS: KDGL IS NOT A POSITIVE, EVEN NUMBER')
151 ENDIF
152 
153 ! Optional arguments
154 
155 ALLOCATE(g%NLOEN(r%NDGL))
156 IF(llp2)WRITE(nout,9) 'NLOEN ',SIZE(g%NLOEN ),shape(g%NLOEN )
157 IF(PRESENT(kloen)) THEN
158  DO jgl=1,r%NDGL
159  IF(kloen(jgl) /= r%NDLON) THEN
160  g%LREDUCED_GRID = .true.
161  EXIT
162  ENDIF
163  ENDDO
164 ENDIF
165 
166 IF (g%LREDUCED_GRID) THEN
167  g%NLOEN(:) = kloen(1:r%NDGL)
168 ELSE
169  g%NLOEN(:) = r%NDLON
170 ENDIF
171 
172 IF(PRESENT(ldsplit)) THEN
173  d%LSPLIT = ldsplit
174 ENDIF
175 
176 IF(PRESENT(kapsets)) THEN
177  d%NAPSETS = kapsets
178 ENDIF
179 
180 IF(PRESENT(ktmax)) THEN
181  r%NTMAX = ktmax
182 ELSE
183  r%NTMAX = r%NSMAX
184 ENDIF
185 IF(r%NTMAX /= r%NSMAX) THEN
186  !This SHOULD work but I don't know how to test it /MH
187  CALL abort_trans('SETUP_TRANS:R%NTMAX /= R%NSMAX HAS NOT BEEN VALIDATED')
188 ENDIF
189 !Temporary?
190 IF(PRESENT(ldlinear_grid)) THEN
191  g%LINEAR_GRID = ldlinear_grid
192 ELSEIF(r%NSMAX > (r%NDLON+3)/3) THEN
193  g%LINEAR_GRID = .true.
194 ENDIF
195 
196 ! Setup resolution dependent structures
197 ! -------------------------------------
198 
199 ! Setup distribution independent dimensions
200 CALL setup_dims
201 
202 ! First part of setup of distributed environment
204 
205 ! Compute Legandre polonomial and Gaussian Latitudes and Weights
206 CALL suleg
207 
208 !CALL GSTATS(1802,0) MPL 2.12.08
209 ! Compute arrays related to grid-point geometry
210 CALL setup_geom
211 
212 ! Second part of setup of distributed environment
213 CALL sump_trans
214 
215 ! Initialize Fast Fourier Transform package
216 CALL sufft
217 !CALL GSTATS(1802,1) MPL 2.12.08
218 
219 
220 IF (lhook) CALL dr_hook('SETUP_TRANS',1,zhook_handle)
221 ! ------------------------------------------------------------------
222 9 FORMAT(1x,'ARRAY ',a10,' ALLOCATED ',8i8)
223 
224 !endif INTERFACE
225 
226 END SUBROUTINE setup_trans
227 
228 
subroutine sump_trans
!$Id mode_top_bound COMMON comconstr r
Definition: comconst.h:7
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
type(distr_type), pointer d
Definition: tpm_distr.F90:152
subroutine suleg
Definition: suleg_mod.F90:4
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
integer, parameter jprb
Definition: parkind1.F90:31
subroutine setup_geom
integer(kind=jpim) msetup0
Definition: tpm_gen.F90:13
subroutine set_resol(KRESOL)
!$Header!c c INCLUDE fxyprim h c c c Fonctions in line c c REAL fyprim REAL rj c c il faut la calculer avant d appeler ces fonctions c c c Fonctions a changer selon x(x) et y(y) choisis.c-----------------------------------------------------------------c c.....ici
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
type(dim_type), dimension(:), allocatable, target dim_resol
Definition: tpm_dim.F90:31
logical lhook
Definition: yomhook.F90:12
subroutine setup_trans(KSMAX, KDGL, KLOEN, LDLINEAR_GRID, LDSPLIT, KAPSETS, KTMAX, KRESOL)
Definition: setup_trans.F90:3
subroutine setup_dims
subroutine sufft
Definition: sufft_mod.F90:4
integer(kind=jpim) nmax_resol
Definition: tpm_gen.F90:14
subroutine dr_hook(CDNAME, KSWITCH, PKEY)
Definition: yomhook.F90:17
type(fft_type), dimension(:), allocatable, target fft_resol
Definition: tpm_fft.F90:13
integer(kind=jpim) ncur_resol
Definition: tpm_gen.F90:15
type(distr_type), dimension(:), allocatable, target distr_resol
Definition: tpm_distr.F90:151
integer, parameter jpim
Definition: parkind1.F90:13
integer(kind=jpim) nout
Definition: tpm_gen.F90:9
integer(kind=jpim) ndef_resol
Definition: tpm_gen.F90:16
subroutine abort_trans(CDTEXT)
type(fields_type), dimension(:), allocatable, target fields_resol
Definition: tpm_fields.F90:22
type(geom_type), dimension(:), allocatable, target geom_resol
integer(kind=jpim) nprintlev
Definition: tpm_gen.F90:11