source: trunk/LMDZ.PLUTO.old/libf/filtrez/inifilr.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

  • Property svn:executable set to *
File size: 16.8 KB
Line 
1      SUBROUTINE inifilr
2c
3c    ... H. Upadhyaya, O.Sharma   ...
4c
5      IMPLICIT NONE
6c
7c     version 3 .....
8
9c     Correction  le 28/10/97    P. Le Van .
10c  -------------------------------------------------------------------
11#include "dimensions.h"
12#include "paramet.h"
13#include "parafilt.h"
14c  -------------------------------------------------------------------
15#include "comgeom.h"
16#include "coefils.h"
17#include "logic.h"
18#include "serre.h"
19
20      REAL  dlonu(iim),dlatu(jjm)
21      REAL  rlamda( iim ),  eignvl( iim )
22c
23
24      REAL    lamdamax,pi,cof
25      INTEGER i,j,modemax,imx,k,kf,ii
26      REAL dymin,dxmin,colat0
27      REAL eignft(iim,iim), coff
28      REAL matriceun,matriceus,matricevn,matricevs,matrinvn,matrinvs
29      COMMON/matrfil/matriceun(iim,iim,nfilun),matriceus(iim,iim,nfilus)
30     ,             , matricevn(iim,iim,nfilvn),matricevs(iim,iim,nfilvs)
31     ,             ,  matrinvn(iim,iim,nfilun),matrinvs (iim,iim,nfilus)
32#ifdef CRAY
33      INTEGER   ISMIN
34      EXTERNAL  ISMIN
35      INTEGER iymin
36      INTEGER ixmineq
37#endif
38      EXTERNAL  inifgn
39c
40c ------------------------------------------------------------
41c   This routine computes the eigenfunctions of the laplacien
42c   on the stretched grid, and the filtering coefficients
43c     
44c  We designate:
45c   eignfn   eigenfunctions of the discrete laplacien
46c   eigenvl  eigenvalues
47c   jfiltn   indexof the last scalar line filtered in NH
48c   jfilts   index of the first line filtered in SH
49c   modfrst  index of the mode from where modes are filtered
50c   modemax  maximum number of modes ( im )
51c   coefil   filtering coefficients ( lamda_max*cos(rlat)/lamda )
52c   sdd      SQRT( dx )
53c     
54c     the modes are filtered from modfrst to modemax
55c     
56c-----------------------------------------------------------
57c
58
59       pi       = 2. * ASIN( 1. )
60
61       DO i = 1,iim
62        dlonu(i) = xprimu( i )
63       ENDDO
64c
65       CALL inifgn(eignvl)
66c
67        print *,' EIGNVL '
68        PRINT 250,eignvl
69250     FORMAT( 1x,5e13.6)
70c
71c compute eigenvalues and eigenfunctions
72c
73c
74c.................................................................
75c
76c  compute the filtering coefficients for scalar lines and
77c  meridional wind v-lines
78c
79c  we filter all those latitude lines where coefil < 1
80c  NO FILTERING AT POLES
81c
82c  colat0 is to be used  when alpha (stretching coefficient)
83c  is set equal to zero for the regular grid case
84c
85c    .......   Calcul  de  colat0   .........
86c     .....  colat0 = minimum de ( 0.5, min dy/ min dx )   ...
87c
88c
89      DO 45 j = 1,jjm
90         dlatu( j ) = rlatu( j ) - rlatu( j+1 )
91 45   CONTINUE
92c
93#ifdef CRAY
94      iymin   = ISMIN( jjm, dlatu, 1 )
95      ixmineq = ISMIN( iim, dlonu, 1 )
96      dymin   = dlatu( iymin )
97      dxmin   = dlonu( ixmineq )
98#else
99      dxmin   =  dlonu(1)
100       DO  i  = 2, iim
101        dxmin = MIN( dxmin,dlonu(i) )
102       ENDDO
103      dymin  = dlatu(1)
104       DO j  = 2, jjm
105        dymin = MIN( dymin,dlatu(j) )
106       ENDDO
107#endif
108c
109c
110      PRINT *, 'TB15 : dymin, dxmin =',dymin,dxmin
111      colat0  =  MIN( 0.5, dymin/dxmin )
112c
113      IF( .NOT.fxyhypb.AND.ysinus )  THEN
114           colat0 = 0.6
115c         ...... a revoir  pour  ysinus !   .......
116           alphax = 0.
117      ENDIF
118c
119      PRINT 50, colat0,alphax
120  50  FORMAT(/15x,' Inifilr colat0 alphax ',2e16.7)
121c
122      IF(alphax.EQ.1. )  THEN
123        PRINT *,' Inifilr  alphax doit etre  <  a 1.  Corriger '
124         STOP
125      ENDIF
126c
127      lamdamax = iim / ( pi * colat0 * ( 1. - alphax ) )
128
129cc                        ... Correction  le 28/10/97  ( P.Le Van ) ..
130c
131      DO 71 i = 2,iim
132       rlamda( i ) = lamdamax/ SQRT( ABS( eignvl(i) ) )
133 71   CONTINUE
134c
135
136      DO 72 j = 1,jjm
137            DO 73 i = 1,iim
138            coefilu( i,j )  = 0.0
139            coefilv( i,j )  = 0.0
140            coefilu2( i,j ) = 0.0
141            coefilv2( i,j ) = 0.0
142 73     CONTINUE
143 72   CONTINUE
144
145c
146c    ... Determination de jfiltnu,jfiltnv,jfiltsu,jfiltsv ....
147c    .........................................................
148c
149       modemax = iim
150
151cccc    imx = modemax - 4 * (modemax/iim)
152
153       imx  = iim
154c
155       PRINT *,' TRUNCATION AT ',imx
156c
157c     Forcing filters: TB22 this was added in some version
158      jfiltnu=2
159      jfiltsu=2
160
161      DO 75 j = 2, jjm/2+1
162       cof = COS( rlatu(j) )/ colat0
163       !PRINT *,' j,cof,expr= ',j,cof,rlamda(imx)*COS(rlatu(j))
164            IF ( cof .LT. 1. ) THEN
165          IF( rlamda(imx) * COS(rlatu(j) ).LT.1. ) jfiltnu= j
166        ENDIF
167
168       cof = COS( rlatu(jjp1-j+1) )/ colat0
169            IF ( cof .LT. 1. ) THEN
170          IF( rlamda(imx) * COS(rlatu(jjp1-j+1) ).LT.1. )
171     $      jfiltsu= jjp1-j+1
172        ENDIF
173 75   CONTINUE
174c
175      DO 76 j = 1, jjm/2
176       cof = COS( rlatv(j) )/ colat0
177            IF ( cof .LT. 1. ) THEN
178          IF( rlamda(imx) * COS(rlatv(j) ).LT.1. ) jfiltnv= j
179        ENDIF
180
181       cof = COS( rlatv(jjm-j+1) )/ colat0
182            IF ( cof .LT. 1. ) THEN
183          IF( rlamda(imx) * COS(rlatv(jjm-j+1) ).LT.1. )
184     $       jfiltsv= jjm-j+1
185        ENDIF
186 76   CONTINUE
187c                                 
188
189      PRINT *,'TB22 jfiltsu ' ,jfiltsu
190      IF( jfiltnu.LE.0 .OR. jfiltnu.GT. jjm/2 +1 )  THEN
191        PRINT *,' jfiltnu en dehors des valeurs acceptables ' ,jfiltnu
192        STOP
193      ENDIF
194
195      IF( jfiltsu.LE.0 .OR. jfiltsu.GT.  jjm  +1 )  THEN
196        PRINT *,' jfiltsu en dehors des valeurs acceptables ' ,jfiltsu
197        STOP
198      ENDIF
199
200      IF( jfiltnv.LE.0 .OR. jfiltnv.GT. jjm/2    )  THEN
201        PRINT *,' jfiltnv en dehors des valeurs acceptables ' ,jfiltnv
202        STOP
203      ENDIF
204
205      IF( jfiltsv.LE.0 .OR. jfiltsv.GT.     jjm  )  THEN
206        PRINT *,' jfiltsv en dehors des valeurs acceptables ' ,jfiltsv
207        STOP
208      ENDIF
209
210       PRINT *,' jfiltnv jfiltsv jfiltnu jfiltsu ' ,
211     *           jfiltnv,jfiltsv,jfiltnu,jfiltsu
212
213c                                 
214c   ... Determination de coefilu,coefilv,n=modfrstu,modfrstv ....
215c................................................................
216c
217c
218      DO 77 j = 1,jjm
219          modfrstu( j ) = iim
220          modfrstv( j ) = iim
221 77   CONTINUE
222c
223      DO 84 j = 2,jfiltnu
224       DO 81 k = 2,modemax
225             cof = rlamda(k) * COS( rlatu(j) )
226         IF ( cof .LT. 1. ) GOTO 82
227 81    CONTINUE
228      GOTO 84
229 82   modfrstu( j ) = k
230c
231          kf = modfrstu( j )
232           DO 83 k = kf , modemax
233        cof = rlamda(k) * COS( rlatu(j) )
234            coefilu(k,j) = cof - 1.
235            coefilu2(k,j) = cof*cof - 1.
236 83    CONTINUE
237 84   CONTINUE
238c                                 
239c
240      DO 89 j = 1,jfiltnv
241c
242       DO 86 k = 2,modemax
243            cof = rlamda(k) * COS( rlatv(j) )
244         IF ( cof .LT. 1. ) GOTO 87
245 86    CONTINUE
246      GOTO 89
247 87   modfrstv( j ) = k
248c
249           kf = modfrstv( j )
250           DO 88 k = kf , modemax
251        cof = rlamda(k) * COS( rlatv(j) )
252            coefilv(k,j) = cof - 1.
253            coefilv2(k,j) = cof*cof - 1.
254 88    CONTINUE
255c
256 89    CONTINUE
257c
258      DO 94 j = jfiltsu,jjm
259       DO 91 k = 2,modemax
260            cof = rlamda(k) * COS( rlatu(j) )
261         IF ( cof .LT. 1. ) GOTO 92
262 91    CONTINUE
263      GOTO 94
264 92   modfrstu( j ) = k
265c
266        kf = modfrstu( j )
267         DO 93 k = kf , modemax
268          cof = rlamda(k) * COS( rlatu(j) )
269          coefilu(k,j) = cof - 1.
270          coefilu2(k,j) = cof*cof - 1.
271 93      CONTINUE
272 94    CONTINUE
273c                                 
274      DO 99 j = jfiltsv,jjm
275       DO 96 k = 2,modemax
276             cof = rlamda(k) * COS( rlatv(j) )
277         IF ( cof .LT. 1. ) GOTO 97
278 96    CONTINUE
279      GOTO 99
280 97   modfrstv( j ) = k
281c
282       kf = modfrstv( j )
283           DO 98 k = kf , modemax
284        cof = rlamda(k) * COS( rlatv(j) )
285            coefilv(k,j) = cof - 1.
286            coefilv2(k,j) = cof*cof - 1.
287 98    CONTINUE
288 99   CONTINUE
289c
290
291       IF(jfiltnv.GE.jjm/2 .OR. jfiltnu.GE.jjm/2)THEN
292
293         IF(jfiltnv.EQ.jfiltsv)jfiltsv=1+jfiltnv
294         IF(jfiltnu.EQ.jfiltsu)jfiltsu=1+jfiltnu
295
296          PRINT *,'jfiltnv jfiltsv jfiltnu jfiltsu' ,
297     *        jfiltnv,jfiltsv,jfiltnu,jfiltsu
298       ENDIF
299
300       PRINT *,'   Modes premiers  v  '
301       PRINT 334,modfrstv
302       PRINT *,'   Modes premiers  u  '
303       PRINT 334,modfrstu
304
305     
306      IF( nfilun.LT. jfiltnu )  THEN
307       PRINT *,' le parametre nfilun utilise pour la matrice ',
308     *   ' matriceun  est trop petit ! '
309       PRINT *,'Le changer dans parafilt.h et le mettre a  ',jfiltnu
310        PRINT *,' Pour information, nfilun,nfilus,nfilvn,nfilvs '
311     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
312     *  ,jfiltnv,jjm-jfiltsv+1
313               STOP
314      ENDIF
315      IF( nfilun.GT. jfiltnu+ 2 )  THEN
316           PRINT *,' le parametre nfilun utilise pour la matrice ',
317     *' matriceun est trop grand ! Gachis de memoire ! '
318       PRINT *,'Le changer dans parafilt.h et le mettre a  ',jfiltnu
319        PRINT *,' Pour information, nfilun,nfilus,nfilvn,nfilvs '
320     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
321     *  ,jfiltnv,jjm-jfiltsv+1
322c              STOP
323      ENDIF
324      IF( nfilus.LT. jjm - jfiltsu +1 )  THEN
325            PRINT *,' le parametre nfilus utilise pour la matrice ',
326     *   ' matriceus  est trop petit !  '
327       PRINT *,' Le changer dans parafilt.h et le mettre a  ',
328     * jjm - jfiltsu + 1
329        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
330     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
331     *  ,jfiltnv,jjm-jfiltsv+1
332               STOP
333      ENDIF
334      IF( nfilus.GT. jjm - jfiltsu + 3 )  THEN
335           PRINT *,' le parametre nfilus utilise pour la matrice ',
336     * ' matriceus  est trop grand ! '
337       PRINT *,' Le changer dans parafilt.h et le mettre a  ' ,
338     * jjm - jfiltsu + 1
339        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
340     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
341     *  ,jfiltnv,jjm-jfiltsv+1
342c              STOP
343      ENDIF
344      IF( nfilvn.LT. jfiltnv )  THEN
345            PRINT *,' le parametre nfilvn utilise pour la matrice ',
346     *   ' matricevn  est trop petit ! ' 
347       PRINT *,'Le changer dans parafilt.h et le mettre a  ',jfiltnv
348        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
349     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
350     *  ,jfiltnv,jjm-jfiltsv+1
351               STOP
352      ENDIF
353      IF( nfilvn.GT. jfiltnv+ 2 )  THEN
354           PRINT *,' le parametre nfilvn utilise pour la matrice ',
355     *' matricevn est trop grand !  Gachis de memoire ! '
356       PRINT *,'Le changer dans parafilt.h et le mettre a  ',jfiltnv
357        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
358     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
359     *  ,jfiltnv,jjm-jfiltsv+1
360c              STOP
361      ENDIF
362      IF( nfilvs.LT. jjm - jfiltsv +1 )  THEN
363            PRINT *,' le parametre nfilvs utilise pour la matrice ',
364     *   ' matricevs  est trop petit !  Le changer dans parafilt.h '
365       PRINT *,' Le changer dans parafilt.h et le mettre a  '
366     * , jjm - jfiltsv + 1
367        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
368     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
369     *  ,jfiltnv,jjm-jfiltsv+1
370               STOP
371      ENDIF
372      IF( nfilvs.GT. jjm - jfiltsv + 3 )  THEN
373           PRINT *,' le parametre nfilvs utilise pour la matrice ',
374     * ' matricevs  est trop grand ! Gachis de memoire ! '
375       PRINT *,' Le changer dans parafilt.h et le mettre a  '
376     *   ,  jjm - jfiltsv + 1
377        PRINT *,' Pour information , nfilun,nfilus,nfilvn,nfilvs '
378     * ,'doivent etre egaux successivement a  ',jfiltnu,jjm-jfiltsu+1
379     *  ,jfiltnv,jjm-jfiltsv+1
380c              STOP
381      ENDIF
382
383
384c   ...................................................................
385c
386c   ... Calcul de la matrice filtre 'matriceu'  pour les champs situes
387c                       sur la grille scalaire                 ........
388c   ...................................................................
389c
390        DO j = 2, jfiltnu
391
392         DO i=1,iim
393          coff = coefilu(i,j)
394          IF( i.LT.modfrstu(j) ) coff = 0.
395           DO k=1,iim
396            eignft(i,k) = eignfnv(k,i) * coff
397           ENDDO
398         ENDDO
399#ifdef CRAY
400         CALL MXM( eignfnv,iim,eignft,iim,matriceun(1,1,j),iim )
401#else
402#ifdef BLAS
403         CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
404     $   eignfnv, iim, eignft, iim, 0.0, matriceun(1,1,j), iim)
405#else
406         DO k = 1, iim
407         DO i = 1, iim
408            matriceun(i,k,j) = 0.0
409            DO ii = 1, iim
410               matriceun(i,k,j) = matriceun(i,k,j)
411     .                          + eignfnv(i,ii)*eignft(ii,k)
412            ENDDO
413         ENDDO
414         ENDDO
415#endif
416#endif
417
418        ENDDO
419
420        DO j = jfiltsu, jjm
421
422         DO i=1,iim
423          coff = coefilu(i,j)
424          IF( i.LT.modfrstu(j) ) coff = 0.
425            DO k=1,iim
426             eignft(i,k) = eignfnv(k,i) * coff
427            ENDDO
428         ENDDO
429#ifdef CRAY
430         CALL MXM(eignfnv,iim,eignft,iim,matriceus(1,1,j-jfiltsu+1),iim)
431#else
432#ifdef BLAS
433      CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
434     $           eignfnv, iim, eignft, iim, 0.0,
435     $           matriceus(1,1,j-jfiltsu+1), iim)
436#else
437         DO k = 1, iim
438         DO i = 1, iim
439            matriceus(i,k,j-jfiltsu+1) = 0.0
440            DO ii = 1, iim
441               matriceus(i,k,j-jfiltsu+1) = matriceus(i,k,j-jfiltsu+1)
442     .                                    + eignfnv(i,ii)*eignft(ii,k)
443            ENDDO
444         ENDDO
445         ENDDO
446#endif
447#endif
448
449        ENDDO
450
451c   ...................................................................
452c
453c   ... Calcul de la matrice filtre 'matricev'  pour les champs situes
454c                       sur la grille   de V ou de Z           ........
455c   ...................................................................
456c
457        DO j = 1, jfiltnv
458
459         DO i = 1, iim
460          coff = coefilv(i,j)
461          IF( i.LT.modfrstv(j) ) coff = 0.
462           DO k = 1, iim
463            eignft(i,k) = eignfnu(k,i) * coff
464           ENDDO
465         ENDDO
466#ifdef CRAY
467          CALL MXM( eignfnu,iim,eignft,iim,matricevn(1,1,j),iim )
468#else
469#ifdef BLAS
470      CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
471     $     eignfnu, iim, eignft, iim, 0.0, matricevn(1,1,j), iim)
472#else
473         DO k = 1, iim
474         DO i = 1, iim
475            matricevn(i,k,j) = 0.0
476            DO ii = 1, iim
477               matricevn(i,k,j) = matricevn(i,k,j)
478     .                          + eignfnu(i,ii)*eignft(ii,k)
479            ENDDO
480         ENDDO
481         ENDDO
482#endif
483#endif
484
485        ENDDO
486
487        DO j = jfiltsv, jjm
488
489         DO i = 1, iim
490          coff = coefilv(i,j)
491          IF( i.LT.modfrstv(j) ) coff = 0.
492            DO k = 1, iim
493             eignft(i,k) = eignfnu(k,i) * coff
494            ENDDO
495         ENDDO
496#ifdef CRAY
497         CALL MXM(eignfnu,iim,eignft,iim,matricevs(1,1,j-jfiltsv+1),iim)
498#else
499#ifdef BLAS
500      CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
501     $           eignfnu, iim, eignft, iim, 0.0,
502     $           matricevs(1,1,j-jfiltsv+1), iim)
503#else
504         DO k = 1, iim
505         DO i = 1, iim
506            matricevs(i,k,j-jfiltsv+1) = 0.0
507            DO ii = 1, iim
508               matricevs(i,k,j-jfiltsv+1) = matricevs(i,k,j-jfiltsv+1)
509     .                          + eignfnu(i,ii)*eignft(ii,k)
510            ENDDO
511         ENDDO
512         ENDDO
513#endif
514#endif
515
516        ENDDO
517
518c   ...................................................................
519c
520c   ... Calcul de la matrice filtre 'matrinv'  pour les champs situes
521c              sur la grille scalaire , pour le filtre inverse ........
522c   ...................................................................
523c
524        DO j = 2, jfiltnu
525
526         DO i = 1,iim
527          coff = coefilu(i,j)/ ( 1. + coefilu(i,j) )
528          IF( i.LT.modfrstu(j) ) coff = 0.
529           DO k=1,iim
530            eignft(i,k) = eignfnv(k,i) * coff
531           ENDDO
532         ENDDO
533#ifdef CRAY
534          CALL MXM( eignfnv,iim,eignft,iim,matrinvn(1,1,j),iim )
535#else
536#ifdef BLAS
537      CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
538     $     eignfnv, iim, eignft, iim, 0.0, matrinvn(1,1,j), iim)
539#else
540         DO k = 1, iim
541         DO i = 1, iim
542            matrinvn(i,k,j) = 0.0
543            DO ii = 1, iim
544               matrinvn(i,k,j) = matrinvn(i,k,j)
545     .                          + eignfnv(i,ii)*eignft(ii,k)
546            ENDDO
547         ENDDO
548         ENDDO
549#endif
550#endif
551
552        ENDDO
553
554        DO j = jfiltsu, jjm
555
556         DO i = 1,iim
557          coff = coefilu(i,j) / ( 1. + coefilu(i,j) )
558          IF( i.LT.modfrstu(j) ) coff = 0.
559            DO k=1,iim
560             eignft(i,k) = eignfnv(k,i) * coff
561            ENDDO
562         ENDDO
563#ifdef CRAY
564         CALL MXM(eignfnv,iim,eignft,iim,matrinvs(1,1,j-jfiltsu+1),iim)
565#else
566#ifdef BLAS
567      CALL SGEMM ('N', 'N', iim, iim, iim, 1.0,
568     $ eignfnv, iim, eignft, iim, 0.0, matrinvs(1,1,j-jfiltsu+1), iim)
569#else
570         DO k = 1, iim
571         DO i = 1, iim
572            matrinvs(i,k,j-jfiltsu+1) = 0.0
573            DO ii = 1, iim
574               matrinvs(i,k,j-jfiltsu+1) = matrinvs(i,k,j-jfiltsu+1)
575     .                          + eignfnv(i,ii)*eignft(ii,k)
576            ENDDO
577         ENDDO
578         ENDDO
579#endif
580#endif
581
582        ENDDO
583
584c   ...................................................................
585
586c
587334    FORMAT(1x,24i3)
588755    FORMAT(1x,6f10.3,i3)
589
590       RETURN
591       END
Note: See TracBrowser for help on using the repository browser.