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

Diff of /trunk/dyn3d/dteta1.f

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

revision 87 by guez, Wed Mar 5 14:57:53 2014 UTC revision 88 by guez, Tue Mar 11 15:09:02 2014 UTC
# Line 1  Line 1 
1  SUBROUTINE dteta1(teta, pbaru, pbarv, dteta)  module dteta1_m
2    
3    ! From LMDZ4/libf/dyn3d/dteta1.F, version 1.1.1.1 2004/05/19 12:53:06    IMPLICIT NONE
   ! Auteurs : P. Le Van, F. Forget  
4    
5    ! Calcul du terme de convergence horizontale du flux d'enthalpie  contains
   ! potentielle.  
6    
7    ! dteta est un argument de sortie pour le s-pg    SUBROUTINE dteta1(teta, pbaru, pbarv, dteta)
8    
9    use dimens_m      ! From LMDZ4/libf/dyn3d/dteta1.F, version 1.1.1.1, 2004/05/19 12:53:06
10    use paramet_m      ! Authors: P. Le Van, F. Forget
   use conf_gcm_m  
   use filtreg_m, only: filtreg  
11    
12    IMPLICIT NONE      ! Calcul du terme de convergence horizontale du flux d'enthalpie
13        ! potentielle.
14    
15        USE dimens_m, ONLY: iim, llm
16        USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmp1, jjp1
17        USE filtreg_m, ONLY: filtreg
18    
19        REAL, intent(in):: teta(ip1jmp1, llm)
20        REAL, intent(in):: pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
21        REAL, intent(out):: dteta(ip1jmp1, llm)
22    
23    REAL, intent(in):: teta(ip1jmp1, llm), pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      ! Local:
24    REAL dteta(ip1jmp1, llm)      INTEGER l, ij
25    INTEGER l, ij      REAL hbyv(ip1jm, llm), hbxu(ip1jmp1, llm)
26    
27    REAL hbyv(ip1jm, llm), hbxu(ip1jmp1, llm)      !----------------------------------------------------------------
28    
29    !----------------------------------------------------------------      DO l = 1, llm
30           DO ij = iip2, ip1jm - 1
31              hbxu(ij, l) = pbaru(ij, l) * 0.5 * (teta(ij, l) + teta(ij + 1, l))
32           end DO
33    
34    DO l = 1, llm         DO ij = iip1+ iip1, ip1jm, iip1
35       DO ij = iip2, ip1jm - 1            hbxu(ij, l) = hbxu(ij - iim, l)
36          hbxu(ij, l) = pbaru(ij, l) * 0.5 * (teta(ij, l) + teta(ij + 1, l))         end DO
      end DO  
37    
38       DO ij = iip1+ iip1, ip1jm, iip1         DO ij = 1, ip1jm
39          hbxu(ij, l) = hbxu(ij - iim, l)            hbyv(ij, l)= pbarv(ij, l) * 0.5 * (teta(ij, l) + teta(ij + iip1, l))
40       end DO         end DO
41        end DO
42    
43       DO ij = 1, ip1jm      CALL convflu(hbxu, hbyv, llm, dteta)
         hbyv(ij, l)= pbarv(ij, l) * 0.5 * (teta(ij, l) + teta(ij + iip1, l))  
      end DO  
   end DO  
44    
45    CALL convflu(hbxu, hbyv, llm, dteta)      ! stockage dans dh de la convergence horizontale filtrée du flux
46        ! d'enthalpie potentielle
47        CALL filtreg(dteta, jjp1, llm, 2, 2, .true.)
48    
49    ! stockage dans dh de la convergence horizont. filtree' du flux    END SUBROUTINE dteta1
   ! d'enthalpie potentielle  
   CALL filtreg(dteta, jjp1, llm, 2, 2, .true.)  
50    
51  END SUBROUTINE dteta1  end module dteta1_m

Legend:
Removed from v.87  
changed lines
  Added in v.88

  ViewVC Help
Powered by ViewVC 1.1.21