Ignore:
Timestamp:
Jul 22, 2024, 9:29:09 PM (4 months ago)
Author:
abarral
Message:

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/filtrez/filtreg_mod.F90

    r5098 r5099  
    1 !
     1
    22! $Id$
    3 !
     3
    44MODULE filtreg_mod
    55
     
    1919
    2020    !    ... H. Upadhyaya, O.Sharma   ...
    21     !
     21
    2222    IMPLICIT NONE
    23     !
     23
    2424    !     version 3 .....
    2525
     
    3434    REAL  dlonu(iim),dlatu(jjm)
    3535    REAL  rlamda( iim ),  eignvl( iim )
    36     !
    3736
    3837    REAL    lamdamax,pi,cof
     
    4746    INTEGER iymin
    4847    INTEGER ixmineq
    49     !
     48
    5049    ! ------------------------------------------------------------
    5150    !   This routine computes the eigenfunctions of the laplacien
    5251    !   on the stretched grid, and the filtering coefficients
    53     !     
     52
    5453    !  We designate:
    5554    !   eignfn   eigenfunctions of the discrete laplacien
     
    6160    !   coefil   filtering coefficients ( lamda_max*COS(rlat)/lamda )
    6261    !   sdd      SQRT( dx )
    63     !     
     62
    6463    !     the modes are filtered from modfrst to modemax
    65     !     
     64
    6665    !-----------------------------------------------------------
    67     !
     66
    6867    if ( iim == 1 ) return ! No filtre in 2D y-z
    6968
     
    7372       dlonu(i) = xprimu( i )
    7473    ENDDO
    75     !
     74
    7675    CALL inifgn(eignvl)
    77     !
     76
    7877    PRINT *,'inifilr: EIGNVL '
    7978    PRINT 250,eignvl
    8079250 FORMAT( 1x,5e14.6)
    81     !
     80
    8281    ! compute eigenvalues and eigenfunctions
    83     !
    84     !
     82
     83
    8584    !.................................................................
    86     !
     85
    8786    !  compute the filtering coefficients for scalar lines and
    8887    !  meridional wind v-lines
    89     !
     88
    9089    !  we filter all those latitude lines WHERE coefil < 1
    9190    !  NO FILTERING AT POLES
    92     !
     91
    9392    !  colat0 is to be used  when alpha (stretching coefficient)
    9493    !  is set equal to zero for the regular grid CASE
    95     !
     94
    9695    !    .......   Calcul  de  colat0   .........
    9796    !     .....  colat0 = minimum de ( 0.5, min dy/ min dx )   ...
    98     !
    99     !
     97
     98
    10099    DO j = 1,jjm
    101100       dlatu( j ) = rlatu( j ) - rlatu( j+1 )
    102101    ENDDO
    103     !
    104102
    105103    dxmin   =  dlonu(1)
     
    111109       dymin = MIN( dymin,dlatu(j) )
    112110    ENDDO
    113     !
     111
    114112    ! For a regular grid, we want the filter to start at latitudes
    115113    ! corresponding to lengths dx of the same size as dy (in terms
     
    118116    ! Same idea for the zoomed grid: start filtering polewards as soon
    119117    ! as length dx becomes of the same size as dy
    120     !
     118
    121119    ! if maxlatfilter >0, prescribe the colat0 value from the .def files
    122120   
     
    125123    colat0  =  MIN( 0.5, dymin/dxmin )
    126124    ! colat0  =  1.
    127     !
     125
    128126    IF( .NOT.fxyhypb.AND.ysinus )  THEN
    129127       colat0 = 0.6
     
    137135
    138136    ENDIF
    139    
    140    
    141    
    142     !
     137
    143138    PRINT 50, colat0,alphax
    14413950  FORMAT(/15x,' Inifilr colat0 alphax ',2e16.7)
    145     !
     140
    146141    IF(alphax==1. )  THEN
    147142       PRINT *,' Inifilr  alphax doit etre  <  a 1.  Corriger '
    148143       STOP
    149144    ENDIF
    150     !
     145
    151146    lamdamax = iim / ( pi * colat0 * ( 1. - alphax ) )
    152147
    153148    !                        ... Correction  le 28/10/97  ( P.Le Van ) ..
    154     !
     149
    155150    DO i = 2,iim
    156151       rlamda( i ) = lamdamax/ SQRT( ABS( eignvl(i) ) )
    157152    ENDDO
    158     !
    159153
    160154    DO j = 1,jjm
     
    167161    ENDDO
    168162
    169     !
    170163    !    ... Determination de jfiltnu,jfiltnv,jfiltsu,jfiltsv ....
    171164    !    .........................................................
    172     !
     165
    173166    modemax = iim
    174167
     
    176169
    177170    imx  = iim
    178     !
     171
    179172    PRINT *,'inifilr: TRUNCATION AT ',imx
    180     !
     173
    181174! Ehouarn: set up some defaults
    182175    jfiltnu=2 ! avoid north pole
     
    200193       ENDIF
    201194    ENDDO
    202     !
     195
    203196    DO j = 1, jjm/2
    204197       cof = COS( rlatv(j) )/ colat0
     
    216209       ENDIF
    217210    ENDDO
    218     !                                 
    219211
    220212    IF( jfiltnu> jjm/2 +1 )  THEN
     
    251243    ENDIF
    252244
    253     !                                 
    254245    !   ... Determination de coefilu,coefilv,n=modfrstu,modfrstv ....
    255246    !................................................................
    256     !
    257     !
     247
     248
    258249    DO j = 1,jjm
    259250    !default initialization: all modes are retained (i.e. no filtering)
     
    261252       modfrstv( j ) = iim
    262253    ENDDO
    263     !
     254
    264255    DO j = 2,jfiltnu
    265256       DO k = 2,modemax
     
    269260       GOTO 84
    27026182     modfrstu( j ) = k
    271        !
     262
    272263       kf = modfrstu( j )
    273264       DO k = kf , modemax
     
    27826984     CONTINUE
    279270    ENDDO
    280     !                                 
    281     !
     271
     272
    282273    DO j = 1,jfiltnv
    283        !
     274
    284275       DO k = 2,modemax
    285276          cof = rlamda(k) * COS( rlatv(j) )
     
    288279       GOTO 89
    28928087     modfrstv( j ) = k
    290        !
     281
    291282       kf = modfrstv( j )
    292283       DO k = kf , modemax
     
    29728889     CONTINUE
    298289    ENDDO
    299     !
     290
    300291    DO j = jfiltsu,jjm
    301292       DO k = 2,modemax
     
    305296       GOTO 94
    30629792     modfrstu( j ) = k
    307        !
     298
    308299       kf = modfrstu( j )
    309300       DO k = kf , modemax
     
    31430594     CONTINUE
    315306    ENDDO
    316     !                                 
     307
    317308    DO j = jfiltsv,jjm
    318309       DO k = 2,modemax
     
    322313       GOTO 99
    32331497     modfrstv( j ) = k
    324        !
     315
    325316       kf = modfrstv( j )
    326317       DO k = kf , modemax
     
    33132299     CONTINUE
    332323    ENDDO
    333     !
    334324
    335325    IF(jfiltnv>=jjm/2 .OR. jfiltnu>=jjm/2)THEN
     
    348338    PRINT 334,modfrstu
    349339
    350     ! 
    351     !   ...................................................................
    352     !
     340    !   ...................................................................
     341
    353342    !   ... Calcul de la matrice filtre 'matriceu'  pour les champs situes
    354343    !                       sur la grille scalaire                 ........
    355344    !   ...................................................................
    356     !
     345
    357346    DO j = 2, jfiltnu
    358347
     
    410399
    411400    !   ...................................................................
    412     !
     401
    413402    !   ... Calcul de la matrice filtre 'matricev'  pour les champs situes
    414403    !                       sur la grille   de V ou de Z           ........
    415404    !   ...................................................................
    416     !
     405
    417406    DO j = 1, jfiltnv
    418407
     
    471460
    472461    !   ...................................................................
    473     !
     462
    474463    !   ... Calcul de la matrice filtre 'matrinv'  pour les champs situes
    475464    !              sur la grille scalaire , pour le filtre inverse ........
    476465    !   ...................................................................
    477     !
     466
    478467    DO j = 2, jfiltnu
    479468
     
    539528    !   ...................................................................
    540529
    541     !
    542530334 FORMAT(1x,24i3)
    543531
Note: See TracChangeset for help on using the changeset viewer.