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

Annotation of /trunk/dyn3d/covcont.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 161 - (hide annotations)
Fri Jul 24 14:27:59 2015 UTC (8 years, 10 months ago) by guez
Original Path: trunk/Sources/dyn3d/covcont.f
File size: 1106 byte(s)
rlon[uv] and rlat[uv] are already in start.nc.

Just encapsulated covcont in a module.

finvmaold was not used in leapfrog. Downgraded it from dummy argument
to local variable of SUBROUTINE integrd.

Simplified handling of mass in integrd: down from five 3-dimensional
arrays (masse, massem1, finvmaold, massescr and finvmasse) to three
(masse, massem1, finvmaold).

1 guez 161 module covcont_m
2 guez 3
3 guez 81 IMPLICIT NONE
4 guez 3
5 guez 161 contains
6 guez 3
7 guez 161 SUBROUTINE covcont(klevel, ucov, vcov, ucont, vcont)
8 guez 3
9 guez 161 ! From LMDZ4/libf/dyn3d/covcont.F, version 1.1.1.1 2004/05/19 12:53:07
10 guez 3
11 guez 161 USE dimens_m
12     USE paramet_m
13     USE comgeom
14     ! =======================================================================
15 guez 3
16 guez 161 ! Auteur: P. Le Van
17     ! -------
18 guez 3
19 guez 161 ! Objet:
20     ! ------
21 guez 81
22 guez 161 ! *********************************************************************
23     ! calcul des compos. contravariantes a partir des comp.covariantes
24     ! ********************************************************************
25 guez 81
26 guez 161 ! =======================================================================
27 guez 81
28    
29 guez 161 INTEGER klevel
30     REAL, INTENT (IN) :: ucov(ip1jmp1, klevel), vcov(ip1jm, klevel)
31     REAL ucont(ip1jmp1, klevel), vcont(ip1jm, klevel)
32     INTEGER l, ij
33 guez 81
34 guez 161
35     DO l = 1, klevel
36    
37     DO ij = iip2, ip1jm
38     ucont(ij, l) = ucov(ij, l)*unscu2(ij)
39     END DO
40    
41     DO ij = 1, ip1jm
42     vcont(ij, l) = vcov(ij, l)*unscv2(ij)
43     END DO
44    
45 guez 81 END DO
46 guez 161 RETURN
47     END SUBROUTINE covcont
48 guez 81
49 guez 161 end module covcont_m

  ViewVC Help
Powered by ViewVC 1.1.21