Ignore:
Timestamp:
Jul 24, 2024, 8:45:54 PM (4 months ago)
Author:
abarral
Message:

fix lmdz_fxy

Location:
LMDZ6/branches/Amaury_dev/libf/grid
Files:
3 added
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/grid/lmdz_fxy_new.f90

    r5118 r5122  
    1 ! This module replaces grid/fxy*.h
     1! This module replaces grid/fxy_new.h
    22
    3 MODULE lmdz_fxy
     3MODULE lmdz_fxy_new
     4  USE comconst_mod, ONLY: pi
     5  USE serre_mod, ONLY: pxo, pyo, alphax, alphay, transx, transy
    46  IMPLICIT NONE; PRIVATE
    5   PUBLIC fxy_new, fxy_reg, fxy_sin, fxy_prim
     7  PUBLIC fx, fxprim, fy, fyprim
     8  INCLUDE "dimensions.h"
     9  INCLUDE "paramet.h"
    610CONTAINS
    7   SUBROUTINE fxy_new(ripx, fx, fxprim, fy, fyprim, ri, rj, bigy)
    8     INCLUDE "dimensions.h"
    9     REAL :: ripx, fx, fxprim, fy, fyprim, ri, rj, bigy
     11  REAL FUNCTION ripx(ri)
     12    REAL, INTENT(IN) :: ri
     13    ripx = (ri - 1.0) * 2. * pi / REAL(iim)
     14  END FUNCTION ripx
    1015
    11     !....stretching in x...
    12     ripx(ri) = (ri - 1.0) * 2. * pi / REAL(iim)
    13     fx  (ri) = ripx(ri) + transx + &
    14             alphax * SIN(ripx(ri) + transx - pxo) - pi
    15     fxprim(ri) = 2. * pi / REAL(iim) * &
    16             (1. + alphax * COS(ripx(ri) + transx - pxo))
     16  REAL FUNCTION fx(ri)
     17    REAL, INTENT(IN) :: ri
     18    fx = ripx(ri) + transx + alphax * SIN(ripx(ri) + transx - pxo) - pi
     19  END FUNCTION fx
    1720
    18     !....stretching in y...
    19     bigy(rj) = 2. * (REAL(jjp1) - rj) * pi / jjm
    20     fy(rj) = (bigy(rj) + transy + &
    21             alphay * SIN(bigy(rj) + transy - pyo)) / 2. - pi / 2.
    22     fyprim(rj) = (pi / jjm) * (1. + &
    23             alphay * COS(bigy(rj) + transy - pyo))
     21  REAL FUNCTION fxprim(ri)
     22    REAL, INTENT(IN) :: ri
     23    fxprim = 2. * pi / REAL(iim) * (1. + alphax * COS(ripx(ri) + transx - pxo))
     24  END FUNCTION fxprim
    2425
    25     ! fy(rj)= pyo-pisjjm*(rj-transy)+coefalpha*SIN(depisjm*(rj-
    26     ! *  transy ))
    27     !   fyprim(rj)= pisjjm-pisjjm*coefy2* COS(depisjm*(rj-transy))
    28     !--------------------------------------------------------------
    29   END SUBROUTINE fxy_new
     26  REAL FUNCTION bigy(rj)
     27    REAL, INTENT(IN) :: rj
     28    bigy = 2. * (REAL(jjp1) - rj) * pi / jjm
     29  END FUNCTION bigy
    3030
    31   SUBROUTINE fxy_reg(fy, fx, fxprim, fyprim, ri, rj)
    32     INCLUDE "dimensions.h"
    33     REAL :: fy, fx, fxprim, fyprim, ri, rj
     31  REAL FUNCTION fy(rj)
     32    REAL, INTENT(IN) :: rj
     33    fy = (bigy(rj) + transy + alphay * SIN(bigy(rj) + transy - pyo)) / 2. - pi / 2.
     34  END FUNCTION fy
    3435
    35     fy    (rj) = pi / REAL(jjm) * (0.5 * REAL(jjm) + 1. - rj)
    36     fyprim(rj) = pi / REAL(jjm)
    37 
    38     ! fy(rj)=ASIN(1.+2.*((1.-rj)/REAL(jjm)))
    39     ! fyprim(rj)=1./SQRT((rj-1.)*(jjm+1.-rj))
    40 
    41     fx    (ri) = 2. * pi / REAL(iim) * (ri - 0.5 * REAL(iim) - 1.)
    42     ! fx    ( ri ) = 2.*pi/REAL(iim) * ( ri - 0.5* ( REAL(iim) + 1.) )
    43     fxprim(ri) = 2. * pi / REAL(iim)
    44     !
    45     !    La valeur de pi est passee par le common/const/ou /const2/ .
    46     !    Sinon, il faut la calculer avant d'appeler ces fonctions .
    47     !
    48     !   ----------------------------------------------------------------
    49     ! Fonctions a changer eventuellement, selon x(x) et y(y) choisis .
    50     !   -----------------------------------------------------------------
    51     !
    52     !    .....  ici, on a l'application particuliere suivante   ........
    53     !
    54     !            **************************************
    55     !            **     x = 2. * pi/iim *  X         **
    56     !            **     y =      pi/jjm *  Y         **
    57     !            **************************************
    58     !
    59     !   ..................................................................
    60     !   ..................................................................
    61     !
    62     !
    63     !
    64     !-----------------------------------------------------------------------
    65 
    66   END SUBROUTINE fxy_reg
    67 
    68   SUBROUTINE fxy_sin(fy, fx, fxprim, fyprim, ri, rj)
    69     REAL :: fy, fx, fxprim, fyprim, ri, rj
    70 
    71     fy(rj) = ASIN(1. + 2. * ((1. - rj) / REAL(jjm)))
    72     fyprim(rj) = 1. / SQRT((rj - 1.) * (jjm + 1. - rj))
    73 
    74     fx    (ri) = 2. * pi / REAL(iim) * (ri - 0.5 * REAL(iim) - 1.)
    75     ! fx    ( ri ) = 2.*pi/REAL(iim) * ( ri - 0.5* ( REAL(iim) + 1.) )
    76     fxprim(ri) = 2. * pi / REAL(iim)
    77     !
    78     !
    79     !    La valeur de pi est passee par le common/const/ou /const2/ .
    80     !    Sinon, il faut la calculer avant d'appeler ces fonctions .
    81     !
    82     !   ----------------------------------------------------------------
    83     ! Fonctions a changer eventuellement, selon x(x) et y(y) choisis .
    84     !   -----------------------------------------------------------------
    85     !
    86     !    .....  ici, on a l'application particuliere suivante   ........
    87     !
    88     !            **************************************
    89     !            **     x = 2. * pi/iim *  X         **
    90     !            **     y =      pi/jjm *  Y         **
    91     !            **************************************
    92     !
    93     !   ..................................................................
    94     !   ..................................................................
    95     !
    96     !
    97     !
    98     !-----------------------------------------------------------------------
    99   END SUBROUTINE fxy_sin
    100 
    101   SUBROUTINE fxy_prim(fy, fx, fxprim, fyprim, ri, rj)
    102     REAL :: fy, fx, fxprim, fyprim, ri, rj
    103 
    104     fy    (rj) = pi / REAL(jjm) * (0.5 * REAL(jjm) + 1. - rj)
    105     fyprim(rj) = pi / REAL(jjm)
    106 
    107     ! fy(rj)=ASIN(1.+2.*((1.-rj)/REAL(jjm)))
    108     ! fyprim(rj)=1./SQRT((rj-1.)*(jjm+1.-rj))
    109 
    110     fx    (ri) = 2. * pi / REAL(iim) * (ri - 0.5 * REAL(iim) - 1.)
    111     ! fx    ( ri ) = 2.*pi/REAL(iim) * ( ri - 0.5* ( REAL(iim) + 1.) )
    112     fxprim(ri) = 2. * pi / REAL(iim)
    113     !
    114     !
    115     !    La valeur de pi est passee par le common/const/ou /const2/ .
    116     !    Sinon, il faut la calculer avant d'appeler ces fonctions .
    117     !
    118     !   ----------------------------------------------------------------
    119     ! Fonctions a changer eventuellement, selon x(x) et y(y) choisis .
    120     !   -----------------------------------------------------------------
    121     !
    122     !    .....  ici, on a l'application particuliere suivante   ........
    123     !
    124     !            **************************************
    125     !            **     x = 2. * pi/iim *  X         **
    126     !            **     y =      pi/jjm *  Y         **
    127     !            **************************************
    128     !
    129     !   ..................................................................
    130     !   ..................................................................
    131     !
    132     !
    133     !
    134     !-----------------------------------------------------------------------
    135   END SUBROUTINE fxy_prim
    136 END MODULE lmdz_fxy
     36  REAL FUNCTION fyprim(rj)
     37    REAL, INTENT(IN) :: rj
     38    fyprim = (pi / jjm) * (1. + alphay * COS(bigy(rj) + transy - pyo))
     39  END FUNCTION fyprim
     40END MODULE lmdz_fxy_new
Note: See TracChangeset for help on using the changeset viewer.