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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 45 - (show annotations)
Wed Apr 27 13:00:12 2011 UTC (13 years ago) by guez
File size: 842 byte(s)
Split file "histwrite.f90" into "histwrite.f90", "histwrite_real.f90"
and "histvar_seq.f90".

Extracted documentation from "psextbar.f" into "psextbar.txt" (out of SVN).

1 SUBROUTINE covnat(klevel,ucov, vcov, unat, vnat )
2
3 ! From LMDZ4/libf/dyn3d/covnat.F,v 1.1.1.1 2004/05/19 12:53:07
4
5 use dimens_m
6 use paramet_m
7 use comgeom
8
9 IMPLICIT NONE
10
11 ! Auteur: F Hourdin Phu LeVan
12 ! Objet:
13 ! calcul des compos. naturelles a partir des comp.covariantes
14
15 INTEGER klevel
16 REAL ucov( ip1jmp1,klevel ), vcov( ip1jm,klevel )
17 REAL unat( ip1jmp1,klevel ), vnat( ip1jm,klevel )
18 INTEGER l,ij
19
20 !------------------------------------------------------------------
21
22 DO l = 1,klevel
23 DO ij = 1, iip1
24 unat (ij,l) =0.
25 END DO
26
27 DO ij = iip2, ip1jm
28 unat( ij,l ) = ucov( ij,l ) / cu(ij)
29 ENDDO
30
31 DO ij = ip1jm+1, ip1jmp1
32 unat (ij,l) =0.
33 END DO
34
35 DO ij = 1,ip1jm
36 vnat( ij,l ) = vcov( ij,l ) / cv(ij)
37 ENDDO
38 ENDDO
39
40 END SUBROUTINE covnat

  ViewVC Help
Powered by ViewVC 1.1.21