Newer
Older

WAUTELET Philippe
committed
!MNH_LIC Copyright 1996-2021 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence

WAUTELET Philippe
committed
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
module mode_write_diachro

WAUTELET Philippe
committed
use mode_msg
implicit none
private
public :: Write_diachro
interface Att_write
procedure Att_write_c0, Att_write_i0, Att_write_x0
end interface
contains

WAUTELET Philippe
committed
! #################################################################
subroutine Write_diachro( tpdiafile, tpbudiachro, tpfields, &

WAUTELET Philippe
committed
tpdates, pvar, osplit, tpflyer )

WAUTELET Philippe
committed
! #################################################################
!
!!**** *WRITE_DIACHRO* - Ecriture d'un enregistrement dans un fichier
!! diachronique (de nom de base HGROUP)
!!
!! PURPOSE
!! -------
!
!!** METHOD
!! ------
!! En fait pour un groupe donne HGROUP, on ecrit systematiquement
! plusieurs enregistrements :
! - 1: HGROUP.TYPE (type d'informations a enregistrer)
! - 2: HGROUP.DIM (dimensions de toutes les matrices a
! enregistrer)
! - 3: HGROUP.TITRE (Nom des processus)
! - 4: HGROUP.UNITE (Unites pour chaque processus)
! - 5: HGROUP.COMMENT (Champ commentaire pour chaque processus)
! - 6: HGROUP.TRAJT (Temps)
! - 7: HGROUP.PROCx (Champ traite . 1 enr./ 1 processus)
! - 8: HGROUP.DATIM (Les differentes dates du modele)
! et pour certains types d'informations on enregistre egalement
! des coordonnees (HGROUP.TRAJX, HGROUP.TRAJY, HGROUP.TRAJZ)
!!
!! EXTERNAL
!! --------
!! None
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! Module
!!
!! REFERENCE
!! ---------
!!
!!
!! AUTHOR
!! ------
!! J. Duron * Laboratoire d'Aerologie *
!!
!!
!! MODIFICATIONS
!! -------------
!! Original 08/01/96
!! Updated PM
!! Modification (N. Asencio) 18/06/99 : the two first dimensions of PMASK
!! are linked to the horizontal grid, FMWRIT is called with 'XY' argument.
!! In standard configuration of the budgets, the mask is written once
!! outside this routine with FMWRIT call. Its record name is 'MASK_nnnn.MASK'
!! So optional PMASK is not used .
!! Modification (J. Duron) 24/06/99 : add logical GPACK to disable the pack option,
!! add the initialization of the dimensions of
!! MASK array in MASK case with write outside the
!! J.Escobar 02/10/2015 modif for JPHEXT(JPVEXT) variable
!! D.Gazen+ G.Delautier 06/2016 modif for ncl files

WAUTELET Philippe
committed
!! P. Wautelet 09/06/2017: name of the variable added to the name of the written field
!! and better comment (true comment + units)
!! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O

WAUTELET Philippe
committed
! P. Wautelet 13/09/2019: budget: simplify and modernize date/time management
! P. Wautelet 13/09/2019: remove never used PMASK optional dummy-argument
! P. Wautelet 28/08/2020: remove TPLUOUTDIA dummy argument
! P. Wautelet 09/10/2020: use new data type tpfields

WAUTELET Philippe
committed
! P. Wautelet 08/12/2020: merge budgets terms with different nbutshift in same group variables
! P. Wautelet 03/03/2021: add tbudiachrometadata type (useful to pass more information to Write_diachro)

WAUTELET Philippe
committed
! P. Wautelet 11/03/2021: remove ptrajx/y/z optional dummy arguments of Write_diachro
! + get the trajectory data for LFI files differently
!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------
!
use modd_aircraft_balloon, only: flyer

WAUTELET Philippe
committed
use modd_budget, only: tbudiachrometadata
use modd_conf, only: lpack
use modd_field, only: tfield_metadata_base
use modd_io, only: tfiledata
use modd_type_date, only: date_time
IMPLICIT NONE
!
!* 0.1 Dummy arguments
! ---------------
TYPE(TFILEDATA), INTENT(IN) :: TPDIAFILE ! file to write

WAUTELET Philippe
committed
type(tbudiachrometadata), intent(in) :: tpbudiachro
class(tfield_metadata_base), dimension(:), intent(in) :: tpfields

WAUTELET Philippe
committed
type(date_time), dimension(:), intent(in) :: tpdates !Used only for LFI files
REAL, DIMENSION(:,:,:,:,:,:), INTENT(IN) :: PVAR

WAUTELET Philippe
committed
logical, intent(in), optional :: osplit
type(flyer), intent(in), optional :: tpflyer
!
!* 0.1 Local variables
! ---------------
logical :: gpack
!------------------------------------------------------------------------------
call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro', 'called' )
gpack = lpack
lpack = .false.

WAUTELET Philippe
committed
#ifdef MNH_IOLFI
if ( tpdiafile%cformat == 'LFI' .or. tpdiafile%cformat == 'LFICDF4' ) &

WAUTELET Philippe
committed
call Write_diachro_lfi( tpdiafile, tpbudiachro, tpfields, tpdates, pvar, tpflyer )

WAUTELET Philippe
committed
#endif
#ifdef MNH_IOCDF4
if ( tpdiafile%cformat == 'NETCDF4' .or. tpdiafile%cformat == 'LFICDF4' ) &

WAUTELET Philippe
committed
call Write_diachro_nc4( tpdiafile, tpbudiachro, tpfields, pvar, osplit, tpflyer )
#endif
lpack = gpack
end subroutine Write_diachro

WAUTELET Philippe
committed
#ifdef MNH_IOLFI
!-----------------------------------------------------------------------------

WAUTELET Philippe
committed
subroutine Write_diachro_lfi( tpdiafile, tpbudiachro, tpfields, tpdates, pvar, tpflyer )

WAUTELET Philippe
committed
use modd_aircraft_balloon, only: flyer

WAUTELET Philippe
committed
use modd_budget, only: NLVL_CATEGORY, NLVL_GROUP, NLVL_SHAPE, nbumask, nbutshift, nbusubwrite, tbudiachrometadata
use modd_field, only: NMNHDIM_ONE, NMNHDIM_UNKNOWN, NMNHDIM_FLYER_TIME, NMNHDIM_NOTLISTED, NMNHDIM_UNUSED, &
TYPECHAR, TYPEINT, TYPEREAL, &
tfield_metadata_base, tfielddata
use modd_io, only: tfiledata

WAUTELET Philippe
committed
use modd_les, only: nles_current_iinf, nles_current_isup, nles_current_jinf, nles_current_jsup, &
nles_k, xles_current_z
use modd_parameters, only: jphext
use modd_time, only: tdtexp, tdtseg
use modd_time_n, only: tdtmod
use modd_type_date, only: date_time
use mode_datetime, only: Datetime_distance
use mode_io_field_write, only: IO_Field_write, IO_Field_write_box

WAUTELET Philippe
committed
use mode_menu_diachro, only: Menu_diachro
use mode_tools_ll, only: Get_globaldims_ll
type(tfiledata), intent(in) :: tpdiafile ! File to write

WAUTELET Philippe
committed
type(tbudiachrometadata), intent(in) :: tpbudiachro
class(tfield_metadata_base), dimension(:), intent(in) :: tpfields
type(date_time), dimension(:), intent(in) :: tpdates
real, dimension(:,:,:,:,:,:), intent(in) :: pvar

WAUTELET Philippe
committed
type(flyer), intent(in), optional :: tpflyer
integer, parameter :: LFITITLELGT = 100
integer, parameter :: LFIUNITLGT = 100
integer, parameter :: LFICOMMENTLGT = 100

WAUTELET Philippe
committed
character(len=:), allocatable :: ycategory
character(len=:), allocatable :: yshape

WAUTELET Philippe
committed
character(len=:), allocatable :: ytype
CHARACTER(LEN=20) :: YCOMMENT
CHARACTER(LEN=3) :: YJ

WAUTELET Philippe
committed
character(len=:), allocatable :: ygroup
character(len=LFITITLELGT), dimension(:), allocatable :: ytitles !Used to respect LFI fileformat
character(len=LFIUNITLGT), dimension(:), allocatable :: yunits !Used to respect LFI fileformat
character(len=LFICOMMENTLGT), dimension(:), allocatable :: ycomments !Used to respect LFI fileformat

WAUTELET Philippe
committed
INTEGER :: ILENG, ILENTITRE, ILENUNITE, ILENCOMMENT

WAUTELET Philippe
committed
integer :: iil, iih, ijl, ijh, ikl, ikh

WAUTELET Philippe
committed
INTEGER :: II, IJ, IK, IT, IN, IP, J, JJ
INTEGER :: INTRAJT, IKTRAJX, IKTRAJY, IKTRAJZ
INTEGER :: ITTRAJX, ITTRAJY, ITTRAJZ
INTEGER :: INTRAJX, INTRAJY, INTRAJZ
INTEGER :: IIMASK, IJMASK, IKMASK, ITMASK, INMASK, IPMASK
INTEGER :: IIMAX_ll, IJMAX_ll ! size of the physical global domain

WAUTELET Philippe
committed
integer :: ji
INTEGER,DIMENSION(:),ALLOCATABLE :: ITABCHAR

WAUTELET Philippe
committed
logical :: gdistributed

WAUTELET Philippe
committed
real, dimension(:,:), allocatable :: ztimes
real, dimension(:,:), allocatable :: zdatime

WAUTELET Philippe
committed
real, dimension(:,:,:), allocatable :: ztrajz
TYPE(TFIELDDATA) :: TZFIELD
type(tfiledata) :: tzfile

WAUTELET Philippe
committed
call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro_lfi', 'called' )

WAUTELET Philippe
committed
tzfile = tpdiafile

WAUTELET Philippe
committed

WAUTELET Philippe
committed
iil = tpbudiachro%nil
iih = tpbudiachro%nih
ijl = tpbudiachro%njl
ijh = tpbudiachro%njh
ikl = tpbudiachro%nkl
ikh = tpbudiachro%nkh

WAUTELET Philippe
committed
ycategory = Trim( tpbudiachro%clevels(NLVL_CATEGORY) )
yshape = Trim( tpbudiachro%clevels(NLVL_SHAPE) )

WAUTELET Philippe
committed
!For backward compatibility of LFI files
if ( tpbudiachro%cdirection == 'I' ) then
ijl = 1
ijh = 1
else if ( tpbudiachro%cdirection == 'J' ) then
iil = 1
iih = 1
end if
!Write only in LFI files
tzfile%cformat = 'LFI'

WAUTELET Philippe
committed

WAUTELET Philippe
committed
!Set ygroup to preserve backward compatibility of LFI files

WAUTELET Philippe
committed
if ( Any( tpbudiachro%clevels(NLVL_GROUP) == [ 'UU', 'VV', 'WW', 'TH', 'TK', 'RV', 'RC', 'RR', 'RI', 'RS', 'RG', 'RH' ] ) &
.or. ( tpbudiachro%clevels(NLVL_GROUP)(1:2) == 'SV' .and. Len_trim( tpbudiachro%clevels(NLVL_GROUP) ) == 5 ) ) then

WAUTELET Philippe
committed
Allocate( character(len=9) :: ygroup )

WAUTELET Philippe
committed
ygroup(:) = Trim( tpbudiachro%clevels(NLVL_GROUP) )
do ji = Len_trim( tpbudiachro%clevels(NLVL_GROUP) ) + 1, 5

WAUTELET Philippe
committed
ygroup(ji : ji) = '_'
end do
Write( ygroup(6:9), '( i4.4 )' ) nbutshift

WAUTELET Philippe
committed
else if ( tpbudiachro%clevels(NLVL_GROUP) == 'RhodJ' ) then

WAUTELET Philippe
committed
Allocate( character(len=9) :: ygroup )

WAUTELET Philippe
committed
if ( tpfields(1)%cmnhname == 'RhodJX' ) then

WAUTELET Philippe
committed
ygroup(1:3) = 'RJX'

WAUTELET Philippe
committed
else if ( tpfields(1)%cmnhname == 'RhodJY' ) then

WAUTELET Philippe
committed
ygroup(1:3) = 'RJY'

WAUTELET Philippe
committed
else if ( tpfields(1)%cmnhname == 'RhodJZ' ) then

WAUTELET Philippe
committed
ygroup(1:3) = 'RJZ'

WAUTELET Philippe
committed
else if ( tpfields(1)%cmnhname == 'RhodJS' ) then

WAUTELET Philippe
committed
ygroup(1:3) = 'RJS'
else

WAUTELET Philippe
committed
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', 'unknown variable ' // Trim( tpfields(1)%cmnhname ) // &
' for group ' // Trim( tpbudiachro%clevels(NLVL_GROUP) ) )

WAUTELET Philippe
committed
end if
ygroup(4:5) = '__'
Write( ygroup(6:9), '( i4.4 )' ) nbutshift

WAUTELET Philippe
committed
else if ( tpbudiachro%nsv > 0 ) then
Allocate( character(len=9) :: ygroup )
Write( ygroup, '( "SV", i3.3, i4.4 )' ) tpbudiachro%nsv, nbutshift
else if ( tpbudiachro%clevels(NLVL_CATEGORY) == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_GROUP)(1:3)/='BU_' ) then
ygroup = Trim( tpfields(1)%cmnhname )

WAUTELET Philippe
committed
else

WAUTELET Philippe
committed
ygroup = Trim( tpbudiachro%clevels(NLVL_GROUP) )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed
!For backward compatibility
if ( Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'Flyers' &

WAUTELET Philippe
committed
.and. Trim( tpbudiachro%clevels(NLVL_SHAPE) ) == 'Vertical_profile' ) then

WAUTELET Philippe
committed
ygroup = Trim( ygroup ) // 'Z'
end if

WAUTELET Philippe
committed
if ( Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'LES_budgets' &

WAUTELET Philippe
committed
.and. Trim( tpbudiachro%clevels(NLVL_SHAPE) ) == 'Cartesian' ) then
if ( tpbudiachro%ltcompress ) then
if ( tpbudiachro%lnorm ) then
ygroup = 'H_' // Trim( ygroup )
else
ygroup = 'A_' // Trim( ygroup )
end if
else
if ( tpbudiachro%lnorm ) then
ygroup = 'E_' // Trim( ygroup )
else
!Nothing to do
end if
end if
!Limit to 10 characters (backward compatibility again...)
if ( Len_trim( ygroup ) > 10 ) ygroup = ygroup(1:10)
end if

WAUTELET Philippe
committed
if ( Trim( tpbudiachro%clevels(NLVL_CATEGORY) ) == 'LES_budgets' &
.and. Trim( tpbudiachro%clevels(NLVL_GROUP) ) == 'Spectrum' ) then

WAUTELET Philippe
committed
if ( tpbudiachro%ltcompress ) then
ygroup = 'T_' // Trim( ygroup )
!Limit to 10 characters (backward compatibility again...)
if ( Len_trim( ygroup ) > 10 ) ygroup = ygroup(1:10)
end if
end if

WAUTELET Philippe
committed
!Recompute old TYPE for backward compatibility

WAUTELET Philippe
committed
if ( ycategory == 'Budgets' ) then
if ( yshape == 'Cartesian' ) then

WAUTELET Philippe
committed
ytype = 'CART'
else
ytype = 'MASK'
end if

WAUTELET Philippe
committed
else if ( ycategory == 'LES_budgets' ) then

WAUTELET Philippe
committed
if ( yshape == 'Cartesian' ) then

WAUTELET Philippe
committed
ytype = 'SSOL'
else
ytype = 'SPXY'
end if

WAUTELET Philippe
committed
else if ( ycategory == 'Flyers' ) then
if ( yshape == 'Point' ) then

WAUTELET Philippe
committed
ytype = 'RSPL'
else
ytype = 'CART'
end if

WAUTELET Philippe
committed
else if ( ycategory == 'Profilers' .or. ycategory == 'Stations' ) then

WAUTELET Philippe
committed
ytype = 'CART'

WAUTELET Philippe
committed
else if ( ycategory == 'Time series' ) then

WAUTELET Philippe
committed
if ( tpbudiachro%licompress ) then
ytype = 'CART'
else
ytype = 'SSOL'
end if
else
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', &
'unknown classification for type of variable '//trim(tpfields(1)%cmnhname) )
ytype = 'UNKN'
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
II = SIZE(PVAR,1)
IJ = SIZE(PVAR,2)

WAUTELET Philippe
committed
if ( ycategory == 'Budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' &
.and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then

WAUTELET Philippe
committed
II=iih-iil+1
IJ=ijh-ijl+1

WAUTELET Philippe
committed
gdistributed = .true.
else
!By default data is already collected on the write process for budgets
gdistributed = .false.
end if
IK = SIZE(PVAR,3)
IT = SIZE(PVAR,4)
IN = SIZE(PVAR,5)
IP = SIZE(PVAR,6)

WAUTELET Philippe
committed
INTRAJT=SIZE(tpdates)
IKTRAJX=0; IKTRAJY=0; IKTRAJZ=0
ITTRAJX=0; ITTRAJY=0; ITTRAJZ=0
INTRAJX=0; INTRAJY=0; INTRAJZ=0

WAUTELET Philippe
committed
IF ( PRESENT( tpflyer ) ) THEN
IKTRAJX = 1
ITTRAJX = SIZE( tpflyer%x )
INTRAJX = 1

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
IKTRAJX = 1
ITTRAJX = 1
INTRAJX = IN

WAUTELET Philippe
committed
IF ( PRESENT( tpflyer ) ) THEN
IKTRAJY = 1
ITTRAJY = SIZE( tpflyer%y )
INTRAJY = 1

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
IKTRAJY = 1
ITTRAJY = 1
INTRAJY = IN

WAUTELET Philippe
committed
IF ( PRESENT( tpflyer ) ) THEN
IKTRAJZ = 1
ITTRAJZ = SIZE( tpflyer%z )
INTRAJZ = 1

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
IKTRAJZ = IK
ITTRAJZ = 1
INTRAJZ = IN
ENDIF
IIMASK=0; IJMASK=0; IKMASK=0; ITMASK=0; INMASK=0; IPMASK=0

WAUTELET Philippe
committed
IF ( tpbudiachro%clevels(NLVL_SHAPE) == 'Mask' ) THEN
! MASK is written outside this routine but the dimensions must be initialized
! the mask is defined on the extended domain
CALL GET_GLOBALDIMS_ll (IIMAX_ll,IJMAX_ll)
IIMASK=IIMAX_ll + 2 * JPHEXT
IJMASK=IJMAX_ll + 2 * JPHEXT
IKMASK=1
ITMASK=nbusubwrite
INMASK=NBUMASK
IPMASK=1
ILENTITRE = LFITITLELGT
ILENUNITE = LFIUNITLGT
ILENCOMMENT = LFICOMMENTLGT
!
! 1er enregistrement TYPE
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TYPE'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TYPE'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPECHAR
TZFIELD%NDIMS = 0
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
CALL IO_Field_write(tzfile,TZFIELD,YTYPE)
!
! 2eme enregistrement DIMENSIONS des MATRICES et LONGUEUR des TABLEAUX de CARACTERES et FLAGS de COMPRESSION sur les DIFFERENTS AXES
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.DIM'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.DIM'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEINT
TZFIELD%NDIMS = 1
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
SELECT CASE(YTYPE)

WAUTELET Philippe
committed
if ( iil < 0 .or. iih < 0 .or. ijl < 0 .or. ijh < 0 .or. ikl < 0 .or. ikh < 0 ) then
call Print_msg( NVERB_FATAL, 'IO', 'Write_diachro_lfi', &
'nil, nih, njl, njh, nkl or nkh not set in tpbudiachro for variable ' // Trim( tpfields(1)%cmnhname ) )
end if
ILENG = 34
ALLOCATE(ITABCHAR(ILENG))
ITABCHAR(1)=ILENTITRE; ITABCHAR(2)=ILENUNITE
ITABCHAR(3)=ILENCOMMENT; ITABCHAR(4)=II
ITABCHAR(5)=IJ; ITABCHAR(6)=IK
ITABCHAR(7)=IT; ITABCHAR(8)=IN

WAUTELET Philippe
committed
ITABCHAR(9)=IP; ITABCHAR(10)=iil
ITABCHAR(11)=ijl; ITABCHAR(12)=ikl
ITABCHAR(13)=iih; ITABCHAR(14)=ijh
ITABCHAR(15)=ikh
ITABCHAR(16)=Merge( 1, 0, tpbudiachro%licompress )
ITABCHAR(17)=Merge( 1, 0, tpbudiachro%ljcompress )
ITABCHAR(18)=Merge( 1, 0, tpbudiachro%lkcompress )

WAUTELET Philippe
committed
IF( tpbudiachro%clevels(NLVL_SHAPE) == 'Mask' )THEN
! ITABCHAR(10)=1; ITABCHAR(11)=1
! ITABCHAR(13)=1; ITABCHAR(14)=1
ITABCHAR(16)=1; ITABCHAR(17)=1
ENDIF
ITABCHAR(19)=INTRAJT; ITABCHAR(20)=IKTRAJX
ITABCHAR(21)=IKTRAJY; ITABCHAR(22)=IKTRAJZ
ITABCHAR(23)=ITTRAJX; ITABCHAR(24)=ITTRAJY
ITABCHAR(25)=ITTRAJZ; ITABCHAR(26)=INTRAJX
ITABCHAR(27)=INTRAJY; ITABCHAR(28)=INTRAJZ
ITABCHAR(29)=IIMASK; ITABCHAR(30)=IJMASK
ITABCHAR(31)=IKMASK; ITABCHAR(32)=ITMASK
ITABCHAR(33)=INMASK; ITABCHAR(34)=IPMASK
CALL IO_Field_write(tzfile,TZFIELD,ITABCHAR)
DEALLOCATE(ITABCHAR)
CASE DEFAULT
ILENG = 25
ALLOCATE(ITABCHAR(ILENG))
ITABCHAR(1)=ILENTITRE; ITABCHAR(2)=ILENUNITE
ITABCHAR(3)=ILENCOMMENT; ITABCHAR(4)=II
ITABCHAR(5)=IJ; ITABCHAR(6)=IK
ITABCHAR(7)=IT; ITABCHAR(8)=IN
ITABCHAR(9)=IP
ITABCHAR(10)=INTRAJT; ITABCHAR(11)=IKTRAJX
ITABCHAR(12)=IKTRAJY; ITABCHAR(13)=IKTRAJZ
ITABCHAR(14)=ITTRAJX; ITABCHAR(15)=ITTRAJY
ITABCHAR(16)=ITTRAJZ; ITABCHAR(17)=INTRAJX
ITABCHAR(18)=INTRAJY; ITABCHAR(19)=INTRAJZ
ITABCHAR(20)=IIMASK; ITABCHAR(21)=IJMASK
ITABCHAR(22)=IKMASK; ITABCHAR(23)=ITMASK
ITABCHAR(24)=INMASK; ITABCHAR(25)=IPMASK
CALL IO_Field_write(tzfile,TZFIELD,ITABCHAR)
DEALLOCATE(ITABCHAR)
END SELECT
!
! 3eme enregistrement TITRE
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TITRE'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TITRE'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPECHAR
TZFIELD%NDIMS = 1
TZFIELD%LTIMEDEP = .FALSE.
allocate( ytitles( ip ) )
ytitles(:) = tpfields(1 : ip)%cmnhname
CALL IO_Field_write(tzfile,TZFIELD,ytitles(:))
deallocate( ytitles )
!
! 4eme enregistrement UNITE
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.UNITE'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.UNITE'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPECHAR
TZFIELD%NDIMS = 1
TZFIELD%LTIMEDEP = .FALSE.
allocate( yunits( ip ) )
yunits(:) = tpfields(1 : ip)%cunits
CALL IO_Field_write(tzfile,TZFIELD,yunits(:))
deallocate( yunits )
!
! 5eme enregistrement COMMENT
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.COMMENT'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.COMMENT'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPECHAR
TZFIELD%NDIMS = 1
TZFIELD%LTIMEDEP = .FALSE.
allocate( ycomments( ip ) )
ycomments(:) = tpfields(1 : ip)%ccomment
CALL IO_Field_write(tzfile,TZFIELD,ycomments(:))
deallocate( ycomments )
!
! 6eme enregistrement PVAR
!
! Dans la mesure ou cette matrice risque d'etre tres volumineuse, on ecrira un
! enregistrement par processus
DO J = 1,IP
if ( All( tpfields(1)%ndimlist(:) /= NMNHDIM_UNKNOWN ) ) then
tzfield%ndimlist(1:5) = tpfields(j)%ndimlist(1:5)
do jj = 1, 5
if ( tzfield%ndimlist(jj) == NMNHDIM_UNUSED ) then
tzfield%ndimlist(jj) = NMNHDIM_ONE
end if
end do
if ( tzfield%ndimlist(4) == NMNHDIM_FLYER_TIME ) tzfield%ndimlist(4) = NMNHDIM_NOTLISTED
tzfield%ndimlist(6:) = NMNHDIM_UNUSED
else
call Print_msg( NVERB_ERROR, 'IO', 'Write_diachro_lfi', &
'some dimensions are unknown for variable '//trim(tpfields(1)%cmnhname) )
end if
YJ = ' '
IF(J < 10)WRITE(YJ,'(I1)')J ; YJ = ADJUSTL(YJ)
IF(J >= 10 .AND. J < 100) THEN
WRITE(YJ,'(I2)')J ; YJ = ADJUSTL(YJ)
ELSE IF(J >= 100 .AND. J < 1000) THEN

WAUTELET Philippe
committed
IF ( gdistributed ) THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.PROC'//YJ

WAUTELET Philippe
committed
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(TZFIELD%CMNHNAME)
TZFIELD%CUNITS = tpfields(j)%cunits

WAUTELET Philippe
committed
TZFIELD%CDIR = 'XY'
TZFIELD%CCOMMENT = TRIM(tpfields(j)%cmnhname)//' - '//TRIM(tpfields(j)%ccomment)//' ('// Trim( tpfields(j)%cunits ) //')'
TZFIELD%NGRID = tpfields(j)%ngrid

WAUTELET Philippe
committed
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 5
TZFIELD%LTIMEDEP = .FALSE.
CALL IO_Field_write_BOX(tzfile,TZFIELD,'BUDGET',PVAR(:,:,:,:,:,J), &

WAUTELET Philippe
committed
iil+JPHEXT,iih+JPHEXT,ijl+JPHEXT,ijh+JPHEXT)

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.PROC'//YJ
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(TZFIELD%CMNHNAME)
TZFIELD%CUNITS = tpfields(j)%cunits
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(tpfields(j)%cmnhname)//' - '//TRIM(tpfields(j)%ccomment)//' ('// Trim( tpfields(j)%cunits ) //')'
TZFIELD%NGRID = tpfields(j)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 5
TZFIELD%LTIMEDEP = .FALSE.
CALL IO_Field_write(tzfile,TZFIELD,PVAR(:,:,:,:,:,J))
tzfield%ndimlist(:) = NMNHDIM_UNKNOWN
ENDDO
!
! 7eme enregistrement TRAJT
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJT'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJT'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 2
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
!NMNHDIM_FLYER_TIME excluded because created only in netCDF/HDF groups (local to each flyer)
if ( tpfields(1)%ndimlist(4) /= NMNHDIM_UNKNOWN .and. tpfields(1)%ndimlist(4) /= NMNHDIM_UNUSED &
.and. tpfields(1)%ndimlist(4) /= NMNHDIM_FLYER_TIME ) then
tzfield%ndimlist(1) = tpfields(1)%ndimlist(4)
tzfield%ndimlist(2) = NMNHDIM_ONE
tzfield%ndimlist(3:) = NMNHDIM_UNUSED
end if

WAUTELET Philippe
committed
!Reconstitute old diachro format
allocate( ztimes( size( tpdates ), 1 ) )
do ji=1,size(tpdates)
call Datetime_distance( tdtexp, tpdates(ji ), ztimes(ji, 1 ) )
end do
call IO_Field_write( tzfile, tzfield, ztimes )

WAUTELET Philippe
committed
!Reset ndimlist
tzfield%ndimlist(:) = NMNHDIM_UNKNOWN

WAUTELET Philippe
committed
deallocate( ztimes )
!
! Dans certains cas
!
!
! 8eme enregistrement TRAJX
!

WAUTELET Philippe
committed
IF(PRESENT(tpflyer))THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJX'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJX'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%x, [1, Size( tpflyer%x), 1] ) )

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJX'
TZFIELD%CSTDNAME = ''
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJX'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
!TRAJX is given in extended domain coordinates (=> +jphext) for backward compatibility

WAUTELET Philippe
committed
CALL IO_Field_write(tzfile,TZFIELD, Real( Reshape( &

WAUTELET Philippe
committed
Spread( source = ( nles_current_iinf + nles_current_isup) / 2 + jphext, dim = 1, ncopies = IN ), &

WAUTELET Philippe
committed
[1, 1, IN] ) ) )
ENDIF
!
! 9eme enregistrement TRAJY
!

WAUTELET Philippe
committed
IF(PRESENT(tpflyer))THEN
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJY'
TZFIELD%CSTDNAME = ''
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJY'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.
CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%y, [1, Size( tpflyer%y), 1] ) )

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJY'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJY'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
!TRAJY is given in extended domain coordinates (=> +jphext) for backward compatibility

WAUTELET Philippe
committed
CALL IO_Field_write(tzfile,TZFIELD, Real( Reshape( &

WAUTELET Philippe
committed
Spread( source = ( nles_current_jinf + nles_current_jsup) / 2 + jphext, dim = 1, ncopies = IN ), &

WAUTELET Philippe
committed
[1, 1, IN] ) ) )
ENDIF
!
! 10eme enregistrement TRAJZ
!

WAUTELET Philippe
committed
IF(PRESENT(tpflyer))THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJZ'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJZ'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
CALL IO_Field_write(tzfile,TZFIELD, Reshape( tpflyer%z, [1, Size( tpflyer%z), 1] ) )

WAUTELET Philippe
committed
ELSE IF ( ycategory == 'LES_budgets' .and. tpbudiachro%clevels(NLVL_SHAPE) == 'Cartesian' ) THEN

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.TRAJZ'
TZFIELD%CSTDNAME = ''
TZFIELD%CLONGNAME = TRIM(ygroup)//'.TRAJZ'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 3
TZFIELD%LTIMEDEP = .FALSE.
Allocate( ztrajz(IK, 1, IN) )
do jj = 1, IK
ztrajz(jj, :, :) = xles_current_z(jj)
end do
CALL IO_Field_write(tzfile,TZFIELD,ztrajz)
Deallocate( ztrajz )
ENDIF
!
! 11eme enregistrement PDATIME
!

WAUTELET Philippe
committed
TZFIELD%CMNHNAME = TRIM(ygroup)//'.DATIM'
TZFIELD%CSTDNAME = ''

WAUTELET Philippe
committed
TZFIELD%CLONGNAME = TRIM(ygroup)//'.DATIM'
TZFIELD%CUNITS = ''
TZFIELD%CDIR = '--'
TZFIELD%CCOMMENT = TRIM(YCOMMENT)
TZFIELD%NGRID = tpfields(1)%ngrid
TZFIELD%NTYPE = TYPEREAL
TZFIELD%NDIMS = 2
TZFIELD%LTIMEDEP = .FALSE.

WAUTELET Philippe
committed
!Reconstitute old diachro format
allocate( zdatime( 16, size(tpdates) ) )
zdatime(1, : ) = tdtexp%nyear
zdatime(2, : ) = tdtexp%nmonth
zdatime(3, : ) = tdtexp%nday
zdatime(4, : ) = tdtexp%xtime
zdatime(5, : ) = tdtseg%nyear
zdatime(6, : ) = tdtseg%nmonth
zdatime(7, : ) = tdtseg%nday
zdatime(8, : ) = tdtseg%xtime
zdatime(9, : ) = tdtmod%nyear
zdatime(10, : ) = tdtmod%nmonth
zdatime(11, : ) = tdtmod%nday
zdatime(12, : ) = tdtmod%xtime
zdatime(13, : ) = tpdates(:)%nyear
zdatime(14, : ) = tpdates(:)%nmonth
zdatime(15, : ) = tpdates(:)%nday
zdatime(16, : ) = tpdates(:)%xtime

WAUTELET Philippe
committed
call IO_Field_write( tzfile, tzfield, zdatime )

WAUTELET Philippe
committed
deallocate( zdatime )

WAUTELET Philippe
committed
call Menu_diachro( tzfile, ygroup )
end subroutine Write_diachro_lfi

WAUTELET Philippe
committed
#endif
#ifdef MNH_IOCDF4

WAUTELET Philippe
committed
!-----------------------------------------------------------------------------

WAUTELET Philippe
committed
subroutine Write_diachro_nc4( tpdiafile, tpbudiachro, tpfields, pvar, osplit, tpflyer )

WAUTELET Philippe
committed
use NETCDF, only: NF90_DEF_DIM, NF90_INQ_DIMID, NF90_INQUIRE_DIMENSION, NF90_NOERR
use modd_aircraft_balloon, only: flyer

WAUTELET Philippe
committed
use modd_budget, only: CNCGROUPNAMES, &
NMAXLEVELS, NLVL_ROOT, NLVL_CATEGORY, NLVL_SUBCATEGORY, NLVL_GROUP, &
NLVL_SHAPE, NLVL_TIMEAVG, NLVL_NORM, NLVL_MASK, &
nbutshift, nbusubwrite, tbudiachrometadata
use modd_conf, only: lcartesian
use modd_field
use modd_io, only: isp, tfiledata
use modd_les, only: cbl_height_def, cles_norm_type, nles_masks, xles_temp_sampling

WAUTELET Philippe
committed
use modd_parameters, only: jphext, NBUNAMELGTMAX, NCOMMENTLGTMAX
use modd_precision, only: CDFINT, MNHREAL_NF90
use modd_type_date, only: date_time
use mode_io_field_write, only: IO_Field_create, IO_Field_write, IO_Field_write_box
use mode_io_tools_nc4, only: IO_Err_handle_nc4
type(tfiledata), intent(in) :: tpdiafile ! File to write

WAUTELET Philippe
committed
type(tbudiachrometadata), intent(in) :: tpbudiachro
class(tfield_metadata_base), dimension(:), intent(in) :: tpfields
real, dimension(:,:,:,:,:,:), intent(in) :: pvar

WAUTELET Philippe
committed
logical, intent(in), optional :: osplit
type(flyer), intent(in), optional :: tpflyer

WAUTELET Philippe
committed
character(len=:), allocatable :: ycategory

WAUTELET Philippe
committed
character(len=:), allocatable :: ylevelname
character(len=:), allocatable :: ylevels

WAUTELET Philippe
committed
character(len=:), allocatable :: yshape
character(len=:), allocatable :: ystdnameprefix

WAUTELET Philippe
committed
integer :: iil, iih, ijl, ijh, ikl, ikh
integer :: idims
integer :: icount
integer :: icorr
integer :: ji
integer :: jl
integer :: jp
integer(kind=CDFINT) :: idimid

WAUTELET Philippe
committed
integer(kind=CDFINT) :: ilen

WAUTELET Philippe
committed
integer(kind=CDFINT) :: istatus
integer(kind=CDFINT) :: ilevelid
integer(kind=CDFINT), dimension(0:NMAXLEVELS) :: ilevelids ! ids of the different groups/levels in the netCDF file
logical :: gdistributed
logical :: gsplit
logical(kind=CDFINT), dimension(0:NMAXLEVELS) :: gleveldefined ! Are the different groups/levels already defined in the netCDF file
type(tfielddata) :: tzfield
type(tfiledata) :: tzfile
call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro_nc4', 'called' )
tzfile = tpdiafile
!Write only in netCDF files
tzfile%cformat = 'NETCDF4'

WAUTELET Philippe
committed
ycategory = Trim( tpbudiachro%clevels(NLVL_CATEGORY) )
yshape = Trim( tpbudiachro%clevels(NLVL_SHAPE) )

WAUTELET Philippe
committed
iil = tpbudiachro%nil
iih = tpbudiachro%nih
ijl = tpbudiachro%njl
ijh = tpbudiachro%njh
ikl = tpbudiachro%nkl
ikh = tpbudiachro%nkh

WAUTELET Philippe
committed
if ( ycategory == 'Budgets' .and. yshape == 'Cartesian' &
.and. .not. tpbudiachro%licompress .and. .not. tpbudiachro%ljcompress ) then

WAUTELET Philippe
committed
gdistributed = .true.
else
!By default data is already collected on the write process for budgets
gdistributed = .false.
end if

WAUTELET Philippe
committed
if ( Present( osplit ) ) then
gsplit = osplit
else
gsplit = .false.
end if
MASTER: if ( isp == tzfile%nmaster_rank) then

WAUTELET Philippe
committed
ilevelids(NLVL_ROOT) = tzfile%nncid

WAUTELET Philippe
committed
gleveldefined(:) = .false.

WAUTELET Philippe
committed

WAUTELET Philippe
committed
do jl = 1, NMAXLEVELS

WAUTELET Philippe
committed
call Move_to_next_level( ilevelids(jl-1), gleveldefined(jl-1), tpbudiachro%lleveluse(jl), &
tpbudiachro%clevels(jl), gleveldefined(jl), ilevelids(jl) )

WAUTELET Philippe
committed
end do

WAUTELET Philippe
committed

WAUTELET Philippe
committed
tzfile%nncid = ilevelids(NLVL_MASK)
ylevels = ''
do jl = NMAXLEVELS, 1, -1
ylevels = Trim( CNCGROUPNAMES(jl) ) // ' ' // ylevels

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(jl) ) then
call Att_write( tpbudiachro%clevels(jl), ilevelids(jl), 'levels', Trim( ylevels ) )

WAUTELET Philippe
committed
ylevels = ''
end if

WAUTELET Philippe
committed
end do
if ( .not. gleveldefined(NLVL_CATEGORY) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_CATEGORY)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_CATEGORY)
call Att_write( ylevelname, ilevelid, 'category', ylevelname )

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_CATEGORY) .and. Len_trim( tpbudiachro%ccomments(NLVL_CATEGORY) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_CATEGORY) )

WAUTELET Philippe
committed
if ( ycategory == 'LES_budgets' ) &
call Att_write( ylevelname, ilevelid, 'temporal_sampling_frequency', xles_temp_sampling )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_SUBCATEGORY) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_SUBCATEGORY)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_SUBCATEGORY)

WAUTELET Philippe
committed

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'subcategory', ylevelname )

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_SUBCATEGORY) .and. Len_trim( tpbudiachro%ccomments(NLVL_SUBCATEGORY) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_SUBCATEGORY) )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_GROUP) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_GROUP)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_GROUP)

WAUTELET Philippe
committed

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'group', ylevelname )

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_GROUP) .and. Len_trim( tpbudiachro%ccomments(NLVL_GROUP) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_GROUP) )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_SHAPE) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_SHAPE)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_SHAPE)
call Att_write( ylevelname, ilevelid, 'shape', ylevelname )

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_SHAPE) .and. Len_trim( tpbudiachro%ccomments(NLVL_SHAPE) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_SHAPE) )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'moving', Merge( 'yes', 'no ', tpbudiachro%lmobile ) )

WAUTELET Philippe
committed
if ( ( ycategory == 'Budgets' .and. yshape == 'Cartesian' ) &

WAUTELET Philippe
committed
.or. ycategory == 'LES_budgets' &

WAUTELET Philippe
committed
.or. tpbudiachro%clevels(NLVL_GROUP) == 'TSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP) == 'ZTSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'min_I_index_in_physical_domain', iil )
call Att_write( ylevelname, ilevelid, 'max_I_index_in_physical_domain', iih )
call Att_write( ylevelname, ilevelid, 'min_J_index_in_physical_domain', ijl )
call Att_write( ylevelname, ilevelid, 'max_J_index_in_physical_domain', ijh )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( ( ycategory == 'Budgets' .and. yshape == 'Cartesian' ) &
.or. tpbudiachro%clevels(NLVL_GROUP) == 'TSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP) == 'ZTSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES' ) then

WAUTELET Philippe
committed
!Disabled for LES_budgets because no real meaning on that case (vertical levels are stored in the level_les variable)
call Att_write( ylevelname, ilevelid, 'min_K_index_in_physical_domain', ikl )
call Att_write( ylevelname, ilevelid, 'max_K_index_in_physical_domain', ikh )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed

WAUTELET Philippe
committed
if ( ( ycategory == 'Budgets' .and. yshape == 'Cartesian' ) &

WAUTELET Philippe
committed
.or. ( ycategory == 'LES_budgets' .and. yshape == 'Cartesian' ) &

WAUTELET Philippe
committed
.or. tpbudiachro%clevels(NLVL_GROUP) == 'TSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP) == 'ZTSERIES' &
.or. tpbudiachro%clevels(NLVL_GROUP)(1:8) == 'XTSERIES' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, &

WAUTELET Philippe
committed
'averaged_in_the_I_direction', Merge( 'yes', 'no ', tpbudiachro%licompress ) )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, &

WAUTELET Philippe
committed
'averaged_in_the_J_direction', Merge( 'yes', 'no ', tpbudiachro%ljcompress ) )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, &

WAUTELET Philippe
committed
'averaged_in_the_K_direction', Merge( 'yes', 'no ', tpbudiachro%lkcompress ) )

WAUTELET Philippe
committed
end if
end if

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_TIMEAVG) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_TIMEAVG)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_TIMEAVG)

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_TIMEAVG) .and. Len_trim( tpbudiachro%ccomments(NLVL_TIMEAVG) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_TIMEAVG) )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'time_averaged', Merge( 'yes', 'no ', tpbudiachro%ltcompress ) )

WAUTELET Philippe
committed
end if

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_NORM) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_NORM)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_NORM)

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_NORM) .and. Len_trim( tpbudiachro%ccomments(NLVL_NORM) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_NORM) )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalized', Merge( 'yes', 'no ', tpbudiachro%lnorm ) )

WAUTELET Philippe
committed
if ( ycategory == 'LES_budgets' .and. yshape == 'Cartesian' ) then
if ( tpbudiachro%lnorm ) then
if ( cles_norm_type == 'NONE' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'none' )
else if ( cles_norm_type == 'CONV' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'convective' )
! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'definition_of_boundary_layer_height', cbl_height_def )
else if ( cles_norm_type == 'EKMA' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'Ekman' )
! cbl_height_def determines how the boundary layer height is computed, which is used in this normalization

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'definition_of_boundary_layer_height', cbl_height_def )
else if ( cles_norm_type == 'MOBU' ) then

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'Monin-Obukhov' )
else
call Print_msg( NVERB_WARNING, 'IO', 'Write_diachro_nc4', Trim( tzfile%cname ) // &

WAUTELET Philippe
committed
': group ' // Trim( tpbudiachro%clevels(NLVL_GROUP) ) // ': unknown normalization' )

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'unknown' )
end if
else

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'normalization', 'none' )
end if

WAUTELET Philippe
committed
end if
end if

WAUTELET Philippe
committed
if ( .not. gleveldefined(NLVL_MASK) ) then

WAUTELET Philippe
committed
ylevelname = tpbudiachro%clevels(NLVL_MASK)

WAUTELET Philippe
committed
ilevelid = ilevelids (NLVL_MASK)

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'mask', ylevelname )

WAUTELET Philippe
committed
if ( tpbudiachro%lleveluse(NLVL_MASK) .and. Len_trim( tpbudiachro%ccomments(NLVL_MASK) ) > 0 ) &
call Att_write( ylevelname, ilevelid, 'comment', tpbudiachro%ccomments(NLVL_MASK) )

WAUTELET Philippe
committed
if ( ycategory == 'Budgets' .and. yshape == 'Mask' ) &

WAUTELET Philippe
committed
call Att_write( ylevelname, ilevelid, 'masks_are_stored_in_variable', tpbudiachro%clevels(NLVL_MASK) )

WAUTELET Philippe
committed
end if
end if MASTER
!Determine the number of dimensions and do some verifications
do jp = 1, Size( tpfields )