source: LMDZ5/branches/LMDZ5-DOFOCO/libf/phylmd/phys_output_var_mod.F90 @ 2087

Last change on this file since 2087 was 1791, checked in by Ehouarn Millour, 11 years ago

Enrichissement et organisation en module de la structure ctrl_out des variables de sortie: ajout des champs description, unité et type_ecrit. Adaptation en conséquence des routines histdef et histwrite.
UG
...................................................

Improvement and transformation into a module of the ctrl_out structure describing output vars. New fields: description, unit and type_ecrit. Creation of new routines histwrite and histdef to take advantage of this structure.
UG

File size: 3.3 KB
Line 
1!
2! phys_local_var_mod.F90 1327 2010-03-17 15:33:56Z idelkadi $
3
4      MODULE phys_output_var_mod
5
6      use dimphy
7! Variables outputs pour les ecritures des sorties
8!======================================================================
9!
10!
11!======================================================================
12! Declaration des variables
13
14      REAL, SAVE, ALLOCATABLE :: snow_o(:), zfra_o(:)
15!$OMP THREADPRIVATE(snow_o, zfra_o)
16      INTEGER, SAVE, ALLOCATABLE ::  itau_con(:)       ! Nombre de pas ou rflag <= 1
17!$OMP THREADPRIVATE(itau_con)
18      REAL, ALLOCATABLE :: bils_ec(:) ! Contribution of energy conservation
19      REAL, ALLOCATABLE :: bils_tke(:) ! Contribution of energy conservation
20      REAL, ALLOCATABLE :: bils_diss(:) ! Contribution of energy conservation
21      REAL, ALLOCATABLE :: bils_kinetic(:) ! bilan de chaleur au sol, kinetic
22      REAL, ALLOCATABLE :: bils_enthalp(:) ! bilan de chaleur au sol
23      REAL, ALLOCATABLE :: bils_latent(:) ! bilan de chaleur au sol
24!$OMP THREADPRIVATE(bils_ec,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
25
26! ug Plein de variables venues de phys_output_mod
27      INTEGER, PARAMETER                           :: nfiles = 6
28      LOGICAL, DIMENSION(nfiles), SAVE             :: clef_files
29      LOGICAL, DIMENSION(nfiles), SAVE             :: clef_stations
30      INTEGER, DIMENSION(nfiles), SAVE             :: lev_files
31      INTEGER, DIMENSION(nfiles), SAVE             :: nid_files
32      INTEGER, DIMENSION(nfiles), SAVE  :: nnid_files
33!$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
34      INTEGER, DIMENSION(nfiles), SAVE :: nnhorim
35
36      INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm
37      INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt
38      REAL, DIMENSION(nfiles), SAVE                :: zoutm
39      CHARACTER(LEN=20), DIMENSION(nfiles), SAVE   :: type_ecri
40!$OMP THREADPRIVATE(nnhorim, nhorim, nvertm, zoutm,type_ecri)
41      CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: type_ecri_files, phys_out_filetypes
42!$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes)
43
44 ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
45      LOGICAL, SAVE                                :: swaero_diag=.FALSE.
46!$OMP THREADPRIVATE(swaero_diag)
47
48      INTEGER, SAVE:: levmin(nfiles) = 1
49      INTEGER, SAVE:: levmax(nfiles)
50!$OMP THREADPRIVATE(levmin, levmax)
51
52  TYPE ctrl_out
53     INTEGER,DIMENSION(nfiles)            :: flag
54     CHARACTER(len=20)                    :: name
55     CHARACTER(len=150)                   :: description
56     CHARACTER(len=20)                    :: unit
57     CHARACTER(len=20),DIMENSION(nfiles)  :: type_ecrit
58  END TYPE ctrl_out
59CONTAINS
60
61!======================================================================
62SUBROUTINE phys_output_var_init
63use dimphy
64
65IMPLICIT NONE
66
67      allocate(snow_o(klon), zfra_o(klon))
68      allocate(itau_con(klon))
69      allocate (bils_ec(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
70
71END SUBROUTINE phys_output_var_init
72
73!======================================================================
74SUBROUTINE phys_output_var_end
75use dimphy
76IMPLICIT NONE
77
78      deallocate(snow_o,zfra_o,itau_con)
79      deallocate (bils_ec,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
80
81END SUBROUTINE phys_output_var_end
82
83END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.