source: trunk/LMDZ.COMMON/libf/dyn3dpar/moyzon_mod.F90 @ 1070

Last change on this file since 1070 was 1056, checked in by slebonnois, 12 years ago

SL: Titan runs ! see DOC/chantiers/commit_importants.log

File size: 2.6 KB
Line 
1      MODULE moyzon_mod
2! Moyennes zonales pour transmission a la physique
3!======================================================================
4! Specifique a Titan
5!
6!======================================================================
7! Declaration des variables
8
9      REAL,ALLOCATABLE,SAVE :: zplevbar_mpi(:,:),zplaybar_mpi(:,:)
10      REAL,ALLOCATABLE,SAVE :: ztfibar_mpi(:,:),zqfibar_mpi(:,:,:)
11      REAL,ALLOCATABLE,SAVE :: zphibar_mpi(:,:),zphisbar_mpi(:)
12      REAL,ALLOCATABLE,SAVE :: zpkbar_mpi(:,:),ztetabar_mpi(:,:)
13
14      REAL,ALLOCATABLE,SAVE :: zplevbar(:,:),zplaybar(:,:)
15      REAL,ALLOCATABLE,SAVE :: ztfibar(:,:),zqfibar(:,:,:)
16      REAL,ALLOCATABLE,SAVE :: zphibar(:,:),zphisbar(:)
17      REAL,ALLOCATABLE,SAVE :: zzlevbar(:,:),zzlaybar(:,:)
18!$OMP THREADPRIVATE(zplevbar,zplaybar,ztfibar,zqfibar)
19!$OMP THREADPRIVATE(zphibar,zphisbar,zzlevbar,zzlaybar)
20
21! pmoy: global averaged pressure...
22! tmoy: global averaged temperature...
23! put here to be transfered to Titan routines...
24! to be changed...
25      REAL,ALLOCATABLE,SAVE :: plevmoy(:),playmoy(:)
26      REAL,ALLOCATABLE,SAVE :: tmoy(:),tetamoy(:),pkmoy(:)
27      INTEGER,ALLOCATABLE,SAVE :: klat(:)
28
29CONTAINS
30
31!======================================================================
32SUBROUTINE moyzon_init
33
34USE dimphy
35USE infotrac, only: nqtot
36IMPLICIT NONE
37    INCLUDE "dimensions.h"
38
39      ALLOCATE(zplevbar_mpi(klon,llm+1),zplaybar_mpi(klon,llm))
40      ALLOCATE(zphibar_mpi(klon,llm),zphisbar_mpi(klon))
41      ALLOCATE(ztfibar_mpi(klon,llm),zqfibar_mpi(klon,llm,nqtot))
42      ALLOCATE(zpkbar_mpi(klon,llm),ztetabar_mpi(klon,llm))
43
44END SUBROUTINE moyzon_init
45
46!======================================================================
47SUBROUTINE moyzon_init_omp(nlon)
48
49USE dimphy
50USE infotrac, only: nqtot
51IMPLICIT NONE
52    INCLUDE "dimensions.h"
53
54      INTEGER :: nlon
55
56      ALLOCATE(zplevbar(nlon,llm+1),zplaybar(nlon,llm))
57      ALLOCATE(zphibar(nlon,llm),zphisbar(nlon))
58      ALLOCATE(ztfibar(nlon,llm),zqfibar(nlon,llm,nqtot))
59      ALLOCATE(zzlevbar(nlon,llm+1),zzlaybar(nlon,llm))
60
61END SUBROUTINE moyzon_init_omp
62
63!======================================================================
64SUBROUTINE moyzon(nlev,var,varbar)
65
66IMPLICIT NONE
67#include "dimensions.h"
68#include "paramet.h"
69
70      INTEGER :: nlev
71      REAL,dimension(iip1,nlev) :: var
72      REAL,dimension(nlev)      :: varbar
73
74      INTEGER :: i
75
76      varbar(:) = 0.
77      do i=1,iim
78        varbar(:)=varbar(:)+var(i,:)/iim
79      enddo
80
81      return
82END SUBROUTINE moyzon
83
84!======================================================================
85      END MODULE moyzon_mod
Note: See TracBrowser for help on using the repository browser.