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

Diff of /trunk/dyn3d/tourpot.f

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

trunk/dyn3d/tourpot.f revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC trunk/dyn3d/tourpot.f90 revision 78 by guez, Wed Feb 5 17:51:07 2014 UTC
# Line 1  Line 1 
1  !  module tourpot_m
 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/tourpot.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $  
 !  
       SUBROUTINE tourpot ( vcov, ucov, massebxy, vorpot )  
2    
3  c=======================================================================    IMPLICIT NONE
 c  
 c   Auteur:  P. Le Van  
 c   -------  
 c  
 c   Objet:  
 c   ------  
 c  
 c    *******************************************************************  
 c    .........      calcul du tourbillon potentiel             .........  
 c    *******************************************************************  
 c  
 c     vcov,ucov,fext et pbarxyfl sont des argum. d'entree pour le s-pg .  
 c             vorpot            est  un argum.de sortie pour le s-pg .  
 c  
 c=======================================================================  
4    
5        use dimens_m  contains
       use paramet_m  
       use conf_gcm_m  
       use comgeom  
       use filtreg_m, only: filtreg  
6    
7        IMPLICIT NONE    SUBROUTINE tourpot(vcov, ucov, massebxy, vorpot)
8    
9        REAL  rot( ip1jm,llm )      ! From LMDZ4/libf/dyn3d/tourpot.F, version 1.1.1.1 2004/05/19 12:53:06
       REAL, intent(in):: vcov( ip1jm,llm ),ucov( ip1jmp1,llm )  
       REAL massebxy( ip1jm,llm ),vorpot( ip1jm,llm )  
10    
11        INTEGER l, ij      ! Auteur : P. Le Van
12        ! Objet : calcul du tourbillon potentiel
13    
14        USE dimens_m, ONLY: iim, jjm, llm
15        USE paramet_m, ONLY: iip1, ip1jm, ip1jmp1
16        USE comgeom, ONLY: fext
17        use filtreg_m, only: filtreg
18    
19        REAL, intent(in):: vcov(ip1jm, llm), ucov(ip1jmp1, llm)
20        REAL, intent(in):: massebxy(ip1jm, llm)
21    
22        real, intent(out):: vorpot(ip1jm, llm)
23        ! = (Filtre(d(vcov)/dx - d(ucov)/dy) + fext) / massebxy
24    
25  c  ... vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy ..      ! Local:
26        REAL rot(ip1jm, llm)
27        INTEGER l, ij
28    
29        !---------------------------------------------------------------
30    
31        ! Calcul du rotationnel du vent puis filtrage
32    
33  c    ........  Calcul du rotationnel du vent V  puis filtrage  ........      DO l = 1, llm
34           DO ij = 1, ip1jm - 1
35              rot(ij, l) = vcov(ij + 1, l) - vcov(ij, l) + ucov(ij + iip1, l) &
36                   - ucov(ij, l)
37           end DO
38    
39        DO 5 l = 1,llm         ! correction pour rot(iip1, j, l)
40           ! rot(iip1, j, l) = rot(1, j, l)
41           DO ij = iip1, ip1jm, iip1
42              rot(ij, l) = rot(ij - iim, l)
43           end DO
44        end DO
45    
46        DO 2 ij = 1, ip1jm - 1      CALL filtreg(rot, jjm, llm, 2, 1, .FALSE.)
       rot( ij,l ) = vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)  
    2  CONTINUE  
47    
48  c    ....  correction pour  rot( iip1,j,l )  .....      DO l = 1, llm
49  c    ....     rot(iip1,j,l) = rot(1,j,l)    .....         DO ij = 1, ip1jm - 1
50              vorpot(ij, l) = (rot(ij, l) + fext(ij)) / massebxy(ij, l)
51           end DO
52    
53  CDIR$ IVDEP         ! correction pour vorpot(iip1, j, l)
54           ! vorpot(iip1, j, l)= vorpot(1, j, l)
55           DO ij = iip1, ip1jm, iip1
56              vorpot(ij, l) = vorpot(ij - iim, l)
57           end DO
58        end DO
59    
60        DO 3 ij = iip1, ip1jm, iip1    END SUBROUTINE tourpot
       rot( ij,l ) = rot( ij -iim, l )  
    3  CONTINUE  
61    
62     5  CONTINUE  end module tourpot_m
   
   
       CALL  filtreg( rot, jjm, llm, 2, 1, .FALSE.)  
   
   
       DO 10 l = 1, llm  
   
       DO 6 ij = 1, ip1jm - 1  
       vorpot( ij,l ) = ( rot(ij,l) + fext(ij) ) / massebxy(ij,l)  
    6  CONTINUE  
   
 c    ..... correction pour  vorpot( iip1,j,l)  .....  
 c    ....   vorpot(iip1,j,l)= vorpot(1,j,l) ....  
 CDIR$ IVDEP  
       DO 8 ij = iip1, ip1jm, iip1  
       vorpot( ij,l ) = vorpot( ij -iim,l )  
    8  CONTINUE  
   
   10  CONTINUE  
   
       RETURN  
       END  

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

  ViewVC Help
Powered by ViewVC 1.1.21