/[lmdze]/trunk/libf/dyn3d/geopot.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/geopot.f90

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

revision 31 by guez, Wed Feb 27 13:16:39 2008 UTC revision 32 by guez, Tue Apr 6 17:52:58 2010 UTC
# Line 1  Line 1 
1  SUBROUTINE geopot(ngrid,teta,pk,pks,phis,phi)  SUBROUTINE geopot(ngrid,teta,pk,pks,phis,phi)
2    
3    ! From libf/dyn3d/geopot.F,v 1.1.1.1 2004/05/19    ! From libf/dyn3d/geopot.F, version 1.1.1.1 2004/05/19
4      ! Author: P. Le Van
5      ! Objet : calcul du géopotentiel aux milieux des couches
6      ! L'integration se fait de bas en haut.
7    
8    USE dimens_m    USE dimens_m
9    USE paramet_m    USE paramet_m
10    
11    IMPLICIT NONE    IMPLICIT NONE
12    
   ! Auteur:  P. Le Van  
   
   ! Objet:  
   ! calcul du geopotentiel aux milieux des couches  
   ! l'integration se fait de bas en haut  
   
13    ! Arguments:    ! Arguments:
14    INTEGER, INTENT (IN):: ngrid    INTEGER, INTENT (IN):: ngrid
15    REAL, INTENT (IN):: teta(ngrid,llm), pks(ngrid)    REAL, INTENT (IN):: teta(ngrid,llm), pks(ngrid)
# Line 25  SUBROUTINE geopot(ngrid,teta,pk,pks,phis Line 22  SUBROUTINE geopot(ngrid,teta,pk,pks,phis
22    
23    ! -----------------------------------------------------------------------    ! -----------------------------------------------------------------------
24    
25    ! calcul de phi au niveau 1 pres du sol  .....    ! calcul de phi au niveau 1 pres du sol
26    DO  ij = 1, ngrid    DO  ij = 1, ngrid
27       phi(ij,1) = phis(ij) + teta(ij,1)*(pks(ij)-pk(ij,1))       phi(ij,1) = phis(ij) + teta(ij,1)*(pks(ij)-pk(ij,1))
28    end DO    end DO
29    
30    ! calcul de phi aux niveaux superieurs  .......    ! calcul de phi aux niveaux superieurs
31    DO l = 2, llm    DO l = 2, llm
32       DO ij = 1, ngrid       DO ij = 1, ngrid
33          phi(ij,l) = phi(ij,l-1) + 0.5 * (teta(ij,l) + teta(ij,l-1)) &          phi(ij,l) = phi(ij,l-1) + 0.5 * (teta(ij,l) + teta(ij,l-1)) &

Legend:
Removed from v.31  
changed lines
  Added in v.32

  ViewVC Help
Powered by ViewVC 1.1.21