source: LMDZ5/trunk/libf/phylmd/phys_output_var_mod.F90 @ 2576

Last change on this file since 2576 was 2538, checked in by Laurent Fairhead, 10 years ago

Computation of heat fluxes associated with solid and liquid precipitations
over ocean and seaice. Quantities are sent to the coupler
LF

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 5.0 KB
Line 
1!
2! phys_local_var_mod.F90 1327 2010-03-17 15:33:56Z idelkadi $
3
4MODULE 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_ech(:) ! Contribution of energy conservation
20  REAL, ALLOCATABLE :: bils_tke(:) ! Contribution of energy conservation
21  REAL, ALLOCATABLE :: bils_diss(:) ! Contribution of energy conservation
22  REAL, ALLOCATABLE :: bils_kinetic(:) ! bilan de chaleur au sol, kinetic
23  REAL, ALLOCATABLE :: bils_enthalp(:) ! bilan de chaleur au sol
24  REAL, ALLOCATABLE :: bils_latent(:) ! bilan de chaleur au sol
25  !$OMP THREADPRIVATE(bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
26
27
28  ! ug Plein de variables venues de phys_output_mod
29  INTEGER, PARAMETER                           :: nfiles = 9
30  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_files
31  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_stations
32  INTEGER, DIMENSION(nfiles), SAVE             :: lev_files
33  INTEGER, DIMENSION(nfiles), SAVE             :: nid_files
34  INTEGER, DIMENSION(nfiles), SAVE  :: nnid_files
35  !$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
36  INTEGER, DIMENSION(nfiles), SAVE :: nnhorim
37
38  INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm
39  INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt
40  REAL, DIMENSION(nfiles), SAVE                :: zoutm
41  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE   :: type_ecri
42  !$OMP THREADPRIVATE(nnhorim, nhorim, nvertm, zoutm,type_ecri)
43  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: type_ecri_files, phys_out_filetypes
44  !$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes)
45  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: phys_out_filenames
46  !$OMP THREADPRIVATE(phys_out_filenames)
47
48  ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
49  !--OB: this needs to be set to TRUE by default and changed back to FALSE after first radiation call
50  !--    and corrected back to TRUE based on output requests
51  LOGICAL, SAVE                                :: swaero_diag=.TRUE.
52  !$OMP THREADPRIVATE(swaero_diag)
53
54  INTEGER, SAVE:: levmin(nfiles) = 1
55  INTEGER, SAVE:: levmax(nfiles)
56  !$OMP THREADPRIVATE(levmin, levmax)
57
58  REAL, SAVE                :: zdtime_moy
59  !$OMP THREADPRIVATE(zdtime_moy)
60
61  LOGICAL, SAVE :: vars_defined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
62
63  REAL, allocatable:: zustr_gwd_hines(:), zvstr_gwd_hines(:) ! (klon)
64  REAL, allocatable:: zustr_gwd_front(:), zvstr_gwd_front(:) ! (klon)
65  REAL, allocatable:: zustr_gwd_rando(:), zvstr_gwd_rando(:) ! (klon)
66  !$OMP THREADPRIVATE(zustr_gwd_hines, zvstr_gwd_hines)
67  !$OMP THREADPRIVATE(zustr_gwd_front, zvstr_gwd_front)
68  !$OMP THREADPRIVATE(zustr_gwd_rando, zvstr_gwd_rando)
69
70  TYPE ctrl_out
71     INTEGER,DIMENSION(nfiles)            :: flag
72     CHARACTER(len=20)                    :: name
73     CHARACTER(len=150)                   :: description
74     CHARACTER(len=20)                    :: unit
75     CHARACTER(len=20),DIMENSION(nfiles)  :: type_ecrit
76  END TYPE ctrl_out
77
78  REAL, SAVE, ALLOCATABLE :: sens_prec_liq_o(:,:), sens_prec_sol_o(:,:)
79  REAL, SAVE, ALLOCATABLE :: lat_prec_liq_o(:,:), lat_prec_sol_o(:,:)
80 !$OMP THREADPRIVATE(sens_prec_liq_o, sens_prec_sol_o,lat_prec_liq_o,lat_prec_sol_o)
81
82CONTAINS
83
84  !======================================================================
85  SUBROUTINE phys_output_var_init
86    use dimphy
87
88    IMPLICIT NONE
89
90    include "clesphys.h"
91
92    !------------------------------------------------
93
94    allocate(snow_o(klon), zfra_o(klon))
95    allocate(itau_con(klon))
96    allocate(sens_prec_liq_o(klon,2))
97    allocate(sens_prec_sol_o(klon,2))
98    allocate(lat_prec_liq_o(klon,2))
99    allocate(lat_prec_sol_o(klon,2))
100    sens_prec_liq_o = 0.0 ; sens_prec_sol_o = 0.0
101    lat_prec_liq_o = 0.0 ; lat_prec_sol_o = 0.0
102
103    allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
104
105    IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon))
106    IF (.not.ok_hines.and.ok_gwd_rando) &
107                  allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon))
108    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
109
110  END SUBROUTINE phys_output_var_init
111
112  !======================================================================
113  SUBROUTINE phys_output_var_end
114    use dimphy
115    IMPLICIT NONE
116
117    deallocate(snow_o,zfra_o,itau_con)
118    deallocate (bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
119
120  END SUBROUTINE phys_output_var_end
121
122END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.