/[lmdze]/trunk/dyn3d/fxysinus.f
ViewVC logotype

Diff of /trunk/dyn3d/fxysinus.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/fxysinus.f revision 39 by guez, Tue Jan 25 15:11:05 2011 UTC trunk/dyn3d/fxysinus.f revision 82 by guez, Wed Mar 5 14:57:53 2014 UTC
# Line 1  Line 1 
1  !  
2  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/fxysinus.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/fxysinus.F,v 1.1.1.1 2004/05/19
3  !  ! 12:53:06 lmdzadmin Exp $
4        SUBROUTINE fxysinus (rlatu,yprimu,rlatv,yprimv,rlatu1,yprimu1,  
5       ,                    rlatu2,yprimu2,  SUBROUTINE fxysinus(rlatu, yprimu, rlatv, yprimv, rlatu1, yprimu1, rlatu2, &
6       ,  rlonu,xprimu,rlonv,xprimv,rlonm025,xprimm025,rlonp025,xprimp025)      yprimu2, rlonu, xprimu, rlonv, xprimv, rlonm025, xprimm025, rlonp025, &
7        xprimp025)
8    
9        use dimens_m  
10        use paramet_m    USE dimens_m
11        use comconst    USE paramet_m
12        use nr_util, only: pi    USE comconst
13        IMPLICIT NONE    USE nr_util, ONLY: pi
14  c    IMPLICIT NONE
15  c     Calcul  des longitudes et des latitudes  pour une fonction f(x,y)  
16  c            avec y = Asin( j )  .    ! Calcul  des longitudes et des latitudes  pour une fonction f(x,y)
17  c    ! avec y = Asin( j )  .
18  c     Auteur  :  P. Le Van  
19  c    ! Auteur  :  P. Le Van
20  c  
21    
22         INTEGER i,j  
23      INTEGER i, j
24         REAL rlatu(jjp1), yprimu(jjp1),rlatv(jjm), yprimv(jjm),  
25       , rlatu1(jjm), yprimu1(jjm), rlatu2(jjm), yprimu2(jjm)    REAL rlatu(jjp1), yprimu(jjp1), rlatv(jjm), yprimv(jjm), rlatu1(jjm), &
26         REAL rlonu(iip1),xprimu(iip1),rlonv(iip1),xprimv(iip1),      yprimu1(jjm), rlatu2(jjm), yprimu2(jjm)
27       , rlonm025(iip1),xprimm025(iip1), rlonp025(iip1),xprimp025(iip1)    REAL rlonu(iip1), xprimu(iip1), rlonv(iip1), xprimv(iip1), rlonm025(iip1), &
28        xprimm025(iip1), rlonp025(iip1), xprimp025(iip1)
29  !  
30  ! $Header: /home/cvsroot/LMDZ4/libf/grid/fxy_sin.h,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $  
31  !    ! $Header: /home/cvsroot/LMDZ4/libf/grid/fxy_sin.h,v 1.1.1.1 2004/05/19
32  c-----------------------------------------------------------------------    ! 12:53:05 lmdzadmin Exp $
33  c INCLUDE 'fxyprim.h'  
34  c    ! -----------------------------------------------------------------------
35  c    ................................................................  
36  c    ................  Fonctions in line  ...........................    ! ................................................................
37  c    ................................................................    ! ................  Fonctions in line  ...........................
38  c    ! ................................................................
39        REAL  fy, fx, fxprim, fyprim  
40        REAL  ri, rj    REAL fy, fx, fxprim, fyprim
41  c    REAL ri, rj
42  c  
43        fy(rj)=ASIN(1.+2.*((1.-rj)/FLOAT(jjm)))  
44        fyprim(rj)=1./SQRT((rj-1.)*(jjm+1.-rj))    fy(rj) = asin(1.+2.*((1.-rj)/float(jjm)))
45      fyprim(rj) = 1./sqrt((rj-1.)*(jjm+1.-rj))
46        fx    ( ri ) = 2.*pi/FLOAT(iim) * ( ri - 0.5*  FLOAT(iim) - 1. )  
47  c     fx    ( ri ) = 2.*pi/FLOAT(iim) * ( ri - 0.5* ( FLOAT(iim) + 1.) )    fx(ri) = 2.*pi/float(iim)*(ri-0.5*float(iim)-1.)
48        fxprim( ri ) = 2.*pi/FLOAT(iim)    ! fx    ( ri ) = 2.*pi/FLOAT(iim) * ( ri - 0.5* ( FLOAT(iim) + 1.) )
49  c    fxprim(ri) = 2.*pi/float(iim)
50  c  
51  c    La valeur de pi est passee par le common/const/ou /const2/ .  
52  c    Sinon, il faut la calculer avant d'appeler ces fonctions .    ! La valeur de pi est passee par le common/const/ou /const2/ .
53  c    ! Sinon, il faut la calculer avant d'appeler ces fonctions .
54  c   ----------------------------------------------------------------  
55  c     Fonctions a changer eventuellement, selon x(x) et y(y) choisis .    ! ----------------------------------------------------------------
56  c   -----------------------------------------------------------------    ! Fonctions a changer eventuellement, selon x(x) et y(y) choisis .
57  c    ! -----------------------------------------------------------------
58  c    .....  ici, on a l'application particuliere suivante   ........  
59  c    ! .....  ici, on a l'application particuliere suivante   ........
60  c                **************************************  
61  c                **     x = 2. * pi/iim *  X         **    ! **************************************
62  c                **     y =      pi/jjm *  Y         **    ! **     x = 2. * pi/iim *  X         **
63  c                **************************************    ! **     y =      pi/jjm *  Y         **
64  c    ! **************************************
65  c   ..................................................................  
66  c   ..................................................................    ! ..................................................................
67  c    ! ..................................................................
68  c  
69  c  
70  c-----------------------------------------------------------------------  
71      ! -----------------------------------------------------------------------
72  c    ......  calcul  des  latitudes  et de y'   .....  
73  c    ! ......  calcul  des  latitudes  et de y'   .....
74         DO j = 1, jjm + 1  
75            rlatu(j) = fy    ( FLOAT( j )        )    DO j = 1, jjm + 1
76           yprimu(j) = fyprim( FLOAT( j )        )      rlatu(j) = fy(float(j))
77         ENDDO      yprimu(j) = fyprim(float(j))
78      END DO
79    
80         DO j = 1, jjm  
81      DO j = 1, jjm
82           rlatv(j)  = fy    ( FLOAT( j ) + 0.5  )  
83           rlatu1(j) = fy    ( FLOAT( j ) + 0.25 )      rlatv(j) = fy(float(j)+0.5)
84           rlatu2(j) = fy    ( FLOAT( j ) + 0.75 )      rlatu1(j) = fy(float(j)+0.25)
85        rlatu2(j) = fy(float(j)+0.75)
86          yprimv(j)  = fyprim( FLOAT( j ) + 0.5  )  
87          yprimu1(j) = fyprim( FLOAT( j ) + 0.25 )      yprimv(j) = fyprim(float(j)+0.5)
88          yprimu2(j) = fyprim( FLOAT( j ) + 0.75 )      yprimu1(j) = fyprim(float(j)+0.25)
89        yprimu2(j) = fyprim(float(j)+0.75)
90         ENDDO  
91      END DO
92  c  
93  c     .....  calcul   des  longitudes et de  x'   .....  
94  c    ! .....  calcul   des  longitudes et de  x'   .....
95         DO i = 1, iim + 1  
96             rlonv(i)     = fx    (   FLOAT( i )          )    DO i = 1, iim + 1
97             rlonu(i)     = fx    (   FLOAT( i ) + 0.5    )      rlonv(i) = fx(float(i))
98          rlonm025(i)     = fx    (   FLOAT( i ) - 0.25  )      rlonu(i) = fx(float(i)+0.5)
99          rlonp025(i)     = fx    (   FLOAT( i ) + 0.25  )      rlonm025(i) = fx(float(i)-0.25)
100        rlonp025(i) = fx(float(i)+0.25)
101           xprimv  (i)    = fxprim (  FLOAT( i )          )  
102           xprimu  (i)    = fxprim (  FLOAT( i ) + 0.5    )      xprimv(i) = fxprim(float(i))
103          xprimm025(i)    = fxprim (  FLOAT( i ) - 0.25   )      xprimu(i) = fxprim(float(i)+0.5)
104          xprimp025(i)    = fxprim (  FLOAT( i ) + 0.25   )      xprimm025(i) = fxprim(float(i)-0.25)
105         ENDDO      xprimp025(i) = fxprim(float(i)+0.25)
106      END DO
107  c  
108         RETURN  
109         END    RETURN
110    END SUBROUTINE fxysinus
111    

Legend:
Removed from v.39  
changed lines
  Added in v.82

  ViewVC Help
Powered by ViewVC 1.1.21