source: LMDZ6/branches/Amaury_dev/libf/grid/lmdz_fxy.f90 @ 5112

Last change on this file since 5112 was 5108, checked in by abarral, 4 months ago

Turn grid/*.h into lmdz_fxy.f90

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.2 KB
Line 
1! This module replaces grid/fxy*.h
2
3MODULE lmdz_fxy
4  IMPLICIT NONE; PRIVATE
5  PUBLIC fxy_new, fxy_reg, fxy_sin, fxy_prim
6CONTAINS
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
10
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))
17
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))
24
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
30
31  SUBROUTINE fxy_reg(fy, fx, fxprim, fyprim, ri, rj)
32    INCLUDE "dimensions.h"
33    REAL :: fy, fx, fxprim, fyprim, ri, rj
34
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
136END MODULE lmdz_fxy
Note: See TracBrowser for help on using the repository browser.