From fc03d9ea7525be854d1f3da3751ff8f239bfbf8e Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Mon, 27 Jan 2020 15:16:09 +0100
Subject: [PATCH] Philippe 27/01/2020: create the tfield_metadata_base abstract
 datatype and use it as a basis for several datatypes

---
 src/LIB/SURCOUCHE/src/modd_field.f90 | 15 +++++++++------
 src/MNH/modd_budget.f90              | 11 ++++++-----
 2 files changed, 15 insertions(+), 11 deletions(-)

diff --git a/src/LIB/SURCOUCHE/src/modd_field.f90 b/src/LIB/SURCOUCHE/src/modd_field.f90
index 58e16d47f..36bf61843 100644
--- a/src/LIB/SURCOUCHE/src/modd_field.f90
+++ b/src/LIB/SURCOUCHE/src/modd_field.f90
@@ -9,6 +9,7 @@
 !  P. Wautelet 12/04/2019: added pointers for C1D, L1D, N1D, X5D and X6D structures in TFIELDDATA
 !  P. Wautelet 12/07/2019: add pointers for T1D structure in TFIELDDATA
 !  P. Wautelet 23/01/2020: split in modd_field.f90 and mode_field.f90
+!  P. Wautelet 27/01/2020: create the tfield_metadata_base abstract datatype
 !-----------------------------------------------------------------
 module modd_field
 
@@ -91,20 +92,15 @@ TYPE TFIELDPTR_T1D
   TYPE(DATE_TIME), DIMENSION(:), POINTER :: DATA => NULL()
 END TYPE TFIELDPTR_T1D
 !
-!Structure describing the characteristics of a field
-TYPE :: TFIELDDATA
+type, abstract :: tfield_metadata_base
   CHARACTER(LEN=NMNHNAMELGTMAX) :: CMNHNAME  = '' !Name of the field (for MesoNH, non CF convention)
   CHARACTER(LEN=NSTDNAMELGTMAX) :: CSTDNAME  = '' !Standard name (CF convention)
   CHARACTER(LEN=32)  :: CLONGNAME = '' !Long name (CF convention)
   CHARACTER(LEN=40)  :: CUNITS    = '' !Canonical units (CF convention)
-  CHARACTER(LEN=2)   :: CDIR      = '' !Type of the data field (XX,XY,--...)
-  CHARACTER(LEN=4)   :: CLBTYPE   = 'NONE' !Type of the lateral boundary (LBX,LBY,LBXU,LBYV)
   CHARACTER(LEN=100) :: CCOMMENT  = '' !Comment (for MesoNH, non CF convention)
   INTEGER            :: NGRID     = NGRIDUNKNOWN !Localization on the model grid
   INTEGER            :: NTYPE     = TYPEUNDEF !Datatype
   INTEGER            :: NDIMS     = 0  !Number of dimensions
-  LOGICAL            :: LTIMEDEP  = .FALSE. !Is the field time-dependent?
-  !
 #if defined(MNH_IOCDF4)
   INTEGER            :: NFILLVALUE =  NF90_FILL_INT  !Fill value for integer fields
   REAL               :: XFILLVALUE =  NF90_FILL_REAL !Fill value for real fields
@@ -119,6 +115,13 @@ TYPE :: TFIELDDATA
   INTEGER            :: NVALIDMAX  =  2147483647 !Maximum valid value for integer fields
   REAL               :: XVALIDMIN  = -1.E36 !Minimum valid value for real fields
   REAL               :: XVALIDMAX  =  1.E36 !Maximum valid value for real fields
+end type tfield_metadata_base
+
+!Structure describing the characteristics of a field
+TYPE, extends( tfield_metadata_base ) :: TFIELDDATA
+  CHARACTER(LEN=2)   :: CDIR      = '' !Type of the data field (XX,XY,--...)
+  CHARACTER(LEN=4)   :: CLBTYPE   = 'NONE' !Type of the lateral boundary (LBX,LBY,LBXU,LBYV)
+  LOGICAL            :: LTIMEDEP  = .FALSE. !Is the field time-dependent?
   !
   TYPE(TFIELDPTR_C0D),DIMENSION(:),ALLOCATABLE :: TFIELD_C0D !Pointer to the character string fields (one per nested mesh)
   TYPE(TFIELDPTR_C1D),DIMENSION(:),ALLOCATABLE :: TFIELD_C1D !Pointer to the character string 1D fields (one per nested mesh)
diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90
index 64aca0931..2ebb8c405 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -46,11 +46,14 @@
 !  P. Wautelet 19/07/2019: parameters to identify budget number
 !  P. Wautelet 15/11/2019: remove unused CBURECORD variable
 !  P. Wautelet 17/01/2020: add new budget data types
+!  P. Wautelet 27/01/2020: use the tfield_metadata_base abstract datatype
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
 !             ------------
-USE MODD_PARAMETERS, ONLY :JPBUMAX, JPBUPROMAX, NBUNAMELGTMAX, NCOMMENTLGTMAX
+
+use modd_field,      only: tfield_metadata_base
+use modd_parameters, only: JPBUMAX, JPBUPROMAX, NBUNAMELGTMAX, NCOMMENTLGTMAX
 
 implicit none
 
@@ -89,8 +92,7 @@ type tbudgetdata
 end type tbudgetdata
 
 
-type tbusourcedata
-  character(len=NBUNAMELGTMAX)  :: cname    = ''
+type, extends( tfield_metadata_base ) :: tbusourcedata
   integer :: ngroup = 0 ! Number of the source term group in which storing the source term
                         !  (0: no store, 1: individual store, >1: number of the group)
   logical :: lenabled   = .false.
@@ -100,8 +102,7 @@ type tbusourcedata
                                   ! It may be true only if the source term is in a group not containing other sources
 end type tbusourcedata
 
-type tbugroupdata
-  character(len=NBUNAMELGTMAX)  :: cname    = ''
+type, extends( tfield_metadata_base ) :: tbugroupdata
   integer :: nsources = 0 ! Number of source terms composing this group
   integer, dimension(:),     allocatable :: nsourcelist ! List of the source terms composing this group
   real,    dimension(:,:,:), allocatable :: xdata ! Array to store the budget data
-- 
GitLab