/[lmdze]/trunk/dyn3d/convflu.f90
ViewVC logotype

Annotation of /trunk/dyn3d/convflu.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (hide annotations)
Thu Jun 13 14:40:06 2019 UTC (5 years ago) by guez
File size: 1337 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 guez 62 SUBROUTINE convflu( xflu,yflu,nbniv,convfl )
2 guez 3
3 guez 62 ! From LMDZ4/libf/dyn3d/convflu.F, version 1.1.1.1 2004/05/19 12:53:05
4    
5     ! P. Le Van
6    
7     ! Calcule la (convergence horiz. * aire locale) du flux ayant pour
8     ! composantes xflu et yflu ,variables extensives .
9    
10     ! nbniv est le nombre de niveaux vert. de xflu et de yflu.
11    
12 guez 265 use dimensions
13 guez 62 use paramet_m
14     use comgeom
15    
16     IMPLICIT NONE
17    
18     integer, intent(in):: nbniv
19     REAL, intent(in):: xflu( ip1jmp1,nbniv ), yflu( ip1jm,nbniv )
20     real, intent(out):: convfl( ip1jmp1,nbniv )
21    
22     real convpn,convps
23     INTEGER l,ij
24     REAL SSUM
25    
26     !------------------------------------------------------------------
27    
28     DO l = 1,nbniv
29     DO ij = iip2, ip1jm - 1
30     convfl( ij + 1,l ) = xflu( ij,l ) - xflu( ij + 1,l ) + &
31     yflu(ij +1,l ) - yflu( ij -iim,l )
32     end DO
33    
34     ! correction pour convfl( 1,j,l)
35     ! convfl(1,j,l)= convfl(iip1,j,l)
36    
37     DO ij = iip2,ip1jm,iip1
38     convfl( ij,l ) = convfl( ij + iim,l )
39     end DO
40    
41     ! calcul aux pĂ´les
42    
43     convpn = SSUM( iim, yflu( 1 ,l ), 1 )
44     convps = - SSUM( iim, yflu( ip1jm-iim,l ), 1 )
45     DO ij = 1,iip1
46     convfl( ij ,l ) = convpn * aire( ij ) / apoln
47     convfl( ij+ ip1jm,l ) = convps * aire( ij+ ip1jm) / apols
48     end DO
49     end DO
50    
51     END SUBROUTINE convflu

  ViewVC Help
Powered by ViewVC 1.1.21