Ignore:
Timestamp:
Jul 17, 2013, 12:20:19 PM (11 years ago)
Author:
Ehouarn Millour
Message:

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:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/phys_output_var_mod.F90

    r1761 r1791  
    1414      REAL, SAVE, ALLOCATABLE :: snow_o(:), zfra_o(:)
    1515!$OMP THREADPRIVATE(snow_o, zfra_o)
    16       INTEGER, save, ALLOCATABLE ::  itau_con(:)       ! Nombre de pas ou rflag <= 1
     16      INTEGER, SAVE, ALLOCATABLE ::  itau_con(:)       ! Nombre de pas ou rflag <= 1
    1717!$OMP THREADPRIVATE(itau_con)
    1818      REAL, ALLOCATABLE :: bils_ec(:) ! Contribution of energy conservation
     
    2424!$OMP THREADPRIVATE(bils_ec,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
    2525
     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
    2635
     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
    2759CONTAINS
    2860
Note: See TracChangeset for help on using the changeset viewer.