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

Diff of /trunk/dyn3d/fxysinus.f

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

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

Legend:
Removed from v.76  
changed lines
  Added in v.97

  ViewVC Help
Powered by ViewVC 1.1.21