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

Contents of /trunk/libf/dyn3d/covnat.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 61 - (show annotations)
Fri Apr 20 14:58:43 2012 UTC (12 years ago) by guez
File size: 1043 byte(s)
No more included file in LMDZE, not even "netcdf.inc".

Created a variable containing the list of common source files in
GNUmakefile. So we now also see clearly files that are specific to
each program.

Split module "histcom". Assembled resulting files in directory
"Histcom".

Removed aliasing in calls to "laplacien".

1 module covnat_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE covnat(klevel, ucov, vcov, unat, vnat)
8
9 ! From LMDZ4/libf/dyn3d/covnat.F, version 1.1.1.1 2004/05/19 12:53:07
10
11 USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmp1
12 USE comgeom, ONLY: cu, cv
13
14 ! Authors: F. Hourdin, Phu Le Van
15
16 ! Objet : calcul des composantes naturelles à partir des
17 ! composantes covariantes.
18
19 INTEGER, intent(in):: klevel
20 REAL, intent(in):: ucov(ip1jmp1, klevel), vcov(ip1jm, klevel)
21 REAL, intent(out):: unat(ip1jmp1, klevel), vnat(ip1jm, klevel)
22
23 ! Local:
24 INTEGER l, ij
25
26 !------------------------------------------------------------------
27
28 DO l = 1, klevel
29 DO ij = 1, iip1
30 unat(ij, l) =0.
31 END DO
32
33 DO ij = iip2, ip1jm
34 unat(ij, l) = ucov(ij, l) / cu(ij)
35 ENDDO
36
37 DO ij = ip1jm+1, ip1jmp1
38 unat(ij, l) =0.
39 END DO
40
41 DO ij = 1, ip1jm
42 vnat(ij, l) = vcov(ij, l) / cv(ij)
43 ENDDO
44 ENDDO
45
46 END SUBROUTINE covnat
47
48 end module covnat_m

  ViewVC Help
Powered by ViewVC 1.1.21