From 754627f25295af187d784840a3b7684f6b3a6a59 Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Fri, 8 Oct 2021 15:25:35 +0200
Subject: [PATCH] Philippe 08/10/2021: remove Fieldlist_nmodel_resize (not
 useful anymore because reallocation are automatically done in Goto_model)

---
 src/LIB/SURCOUCHE/src/modd_field.f90 |   1 -
 src/LIB/SURCOUCHE/src/mode_field.f90 | 439 +--------------------------
 src/MNH/ini_segn.f90                 |   8 +-
 3 files changed, 3 insertions(+), 445 deletions(-)

diff --git a/src/LIB/SURCOUCHE/src/modd_field.f90 b/src/LIB/SURCOUCHE/src/modd_field.f90
index 81aef5eb5..277e8ad08 100644
--- a/src/LIB/SURCOUCHE/src/modd_field.f90
+++ b/src/LIB/SURCOUCHE/src/modd_field.f90
@@ -241,7 +241,6 @@ TYPE, extends( tfield_metadata_base ) :: TFIELDDATA
   TYPE(TFIELDPTR_T1D),DIMENSION(:),ALLOCATABLE :: TFIELD_T1D !Pointer to the date/time 1D fields (one per nested mesh)
 END TYPE TFIELDDATA
 !
-integer, save :: NMODEL_ALLOCATED = 0
 integer, save :: NFIELDS_USED = 0
 LOGICAL, SAVE :: LFIELDLIST_ISINIT = .FALSE.
 TYPE(TFIELDDATA),DIMENSION(MAXFIELDS),SAVE :: TFIELDLIST
diff --git a/src/LIB/SURCOUCHE/src/mode_field.f90 b/src/LIB/SURCOUCHE/src/mode_field.f90
index fac837573..42b139e95 100644
--- a/src/LIB/SURCOUCHE/src/mode_field.f90
+++ b/src/LIB/SURCOUCHE/src/mode_field.f90
@@ -15,7 +15,7 @@
 !  P. Wautelet 19/06/2019: add Fieldlist_nmodel_resize subroutine + provide KMODEL to INI_FIELD_LIST when known
 !  P. Wautelet 23/01/2020: split in modd_field.f90 and mode_field.f90
 !  JL Redelsperger 03/2021: add variables for Ocean LES and auto-coupled version
-!  P. Wautelet 08/10/2021: add Goto_model_1field + Add_field2list procedures
+!  P. Wautelet 08/10/2021: add Goto_model_1field + Add_field2list procedures + remove Fieldlist_nmodel_resize
 !-----------------------------------------------------------------
 module mode_field
 
@@ -34,7 +34,6 @@ public :: Ini_field_list
 public :: Find_field_id_from_mnhname
 public :: Alloc_field_scalars
 public :: Fieldlist_goto_model
-public :: Fieldlist_nmodel_resize
 public :: Ini_field_scalars
 
 interface Goto_model_1field
@@ -89,7 +88,6 @@ ELSE
   !NMODEL is not necessary known here => allocating for max allowed number of models
   !WARNING: if known, the value could change after this subroutine (ie for a restart
   !         with more models) because READ_DESFM_n is called before READ_EXSEG_n
-  !Structures can be resized with a call to Fieldlist_nmodel_resize
   IMODEL = JPMODELMAX
 END IF
 !
@@ -100,8 +98,6 @@ if ( imodel > JPMODELMAX ) &
 WRITE(YMSG,'("allocating fields for up to ",I4," model(s)")') IMODEL
 CALL PRINT_MSG(NVERB_DEBUG,'GEN','INI_FIELD_LIST',YMSG)
 !
-NMODEL_ALLOCATED = IMODEL
-!
 call Add_field2list( TFIELDDATA( &
   CMNHNAME   = 'MNHVERSION',     &
   CSTDNAME   = '',               &
@@ -3385,9 +3381,6 @@ IF (.NOT.LFIELDLIST_ISINIT) THEN
   RETURN
 END IF
 !
-if (kfrom > nmodel_allocated .or. kto > nmodel_allocated ) &
-  call Print_msg( NVERB_FATAL, 'GEN', 'FIELDLIST_GOTO_MODEL', 'kfrom or kto > nmodel_allocated' )
-!
 ! MODD_FIELD_n variables
 !
 call Goto_model_1field( 'ZWS',   kfrom, kto, xzws   )
@@ -4843,434 +4836,4 @@ end if
 
 end subroutine Extend_1field_x6d
 
-
-subroutine Fieldlist_nmodel_resize( kmodelnew )
-
-implicit none
-
-integer, intent(in) :: kmodelnew
-
-character(len=10) :: ymsg
-integer           :: imodelmax
-integer           :: ji, jj
-type(tfieldptr_c0d), dimension(:), allocatable :: tfield_save_c0d
-type(tfieldptr_c1d), dimension(:), allocatable :: tfield_save_c1d
-type(tfieldptr_l0d), dimension(:), allocatable :: tfield_save_l0d
-type(tfieldptr_l1d), dimension(:), allocatable :: tfield_save_l1d
-type(tfieldptr_n0d), dimension(:), allocatable :: tfield_save_n0d
-type(tfieldptr_n1d), dimension(:), allocatable :: tfield_save_n1d
-type(tfieldptr_n2d), dimension(:), allocatable :: tfield_save_n2d
-type(tfieldptr_n3d), dimension(:), allocatable :: tfield_save_n3d
-type(tfieldptr_x0d), dimension(:), allocatable :: tfield_save_x0d
-type(tfieldptr_x1d), dimension(:), allocatable :: tfield_save_x1d
-type(tfieldptr_x2d), dimension(:), allocatable :: tfield_save_x2d
-type(tfieldptr_x3d), dimension(:), allocatable :: tfield_save_x3d
-type(tfieldptr_x4d), dimension(:), allocatable :: tfield_save_x4d
-type(tfieldptr_x5d), dimension(:), allocatable :: tfield_save_x5d
-type(tfieldptr_x6d), dimension(:), allocatable :: tfield_save_x6d
-type(tfieldptr_t0d), dimension(:), allocatable :: tfield_save_t0d
-
-write( ymsg, '( i4,"->",i4 )') nmodel_allocated, kmodelnew
-call Print_msg( NVERB_DEBUG, 'GEN', 'Fieldlist_nmodel_resize', trim( ymsg ) )
-
-!Nothing to do
-if ( kmodelnew == nmodel_allocated ) return
-
-imodelmax = max( kmodelnew, nmodel_allocated )
-
-allocate( tfield_save_c0d( imodelmax ) )
-allocate( tfield_save_c1d( imodelmax ) )
-allocate( tfield_save_l0d( imodelmax ) )
-allocate( tfield_save_l1d( imodelmax ) )
-allocate( tfield_save_n0d( imodelmax ) )
-allocate( tfield_save_n1d( imodelmax ) )
-allocate( tfield_save_n2d( imodelmax ) )
-allocate( tfield_save_n3d( imodelmax ) )
-allocate( tfield_save_x0d( imodelmax ) )
-allocate( tfield_save_x1d( imodelmax ) )
-allocate( tfield_save_x2d( imodelmax ) )
-allocate( tfield_save_x3d( imodelmax ) )
-allocate( tfield_save_x4d( imodelmax ) )
-allocate( tfield_save_x5d( imodelmax ) )
-allocate( tfield_save_x6d( imodelmax ) )
-allocate( tfield_save_t0d( imodelmax ) )
-
-do ji = 1, imodelmax
-  tfield_save_c0d(ji)%data => null()
-  tfield_save_c1d(ji)%data => null()
-  tfield_save_l0d(ji)%data => null()
-  tfield_save_l1d(ji)%data => null()
-  tfield_save_n0d(ji)%data => null()
-  tfield_save_n1d(ji)%data => null()
-  tfield_save_n2d(ji)%data => null()
-  tfield_save_n3d(ji)%data => null()
-  tfield_save_x0d(ji)%data => null()
-  tfield_save_x1d(ji)%data => null()
-  tfield_save_x2d(ji)%data => null()
-  tfield_save_x3d(ji)%data => null()
-  tfield_save_x4d(ji)%data => null()
-  tfield_save_x5d(ji)%data => null()
-  tfield_save_x6d(ji)%data => null()
-  tfield_save_t0d(ji)%data => null()
-end do
-
-do ji = 1, size( tfieldlist )
-  if ( allocated( tfieldlist(ji)%tfield_c0d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_c0d(jj)%data => tfieldlist(ji)%tfield_c0d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_c0d )
-    allocate(   tfieldlist(ji)%tfield_c0d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_c0d(jj)%data => tfield_save_c0d(jj)%data
-      tfield_save_c0d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_c0d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_c0d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_c1d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_c1d(jj)%data => tfieldlist(ji)%tfield_c1d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_c1d )
-    allocate(   tfieldlist(ji)%tfield_c1d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_c1d(jj)%data => tfield_save_c1d(jj)%data
-      tfield_save_c1d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_c1d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_c1d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_l0d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_l0d(jj)%data => tfieldlist(ji)%tfield_l0d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_l0d )
-    allocate(   tfieldlist(ji)%tfield_l0d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_l0d(jj)%data => tfield_save_l0d(jj)%data
-      tfield_save_l0d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_l0d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_l0d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_l1d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_l1d(jj)%data => tfieldlist(ji)%tfield_l1d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_l1d )
-    allocate(   tfieldlist(ji)%tfield_l1d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_l1d(jj)%data => tfield_save_l1d(jj)%data
-      tfield_save_l1d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_l1d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_l1d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_n0d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_n0d(jj)%data => tfieldlist(ji)%tfield_n0d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_n0d )
-    allocate(   tfieldlist(ji)%tfield_n0d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_n0d(jj)%data => tfield_save_n0d(jj)%data
-      tfield_save_n0d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_n0d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_n0d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_n1d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_n1d(jj)%data => tfieldlist(ji)%tfield_n1d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_n1d )
-    allocate(   tfieldlist(ji)%tfield_n1d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_n1d(jj)%data => tfield_save_n1d(jj)%data
-      tfield_save_n1d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_n1d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_n1d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_n2d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_n2d(jj)%data => tfieldlist(ji)%tfield_n2d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_n2d )
-    allocate(   tfieldlist(ji)%tfield_n2d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_n2d(jj)%data => tfield_save_n2d(jj)%data
-      tfield_save_n2d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_n2d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_n2d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_n3d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_n3d(jj)%data => tfieldlist(ji)%tfield_n3d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_n3d )
-    allocate(   tfieldlist(ji)%tfield_n3d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_n3d(jj)%data => tfield_save_n3d(jj)%data
-      tfield_save_n3d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_n3d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_n3d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x0d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x0d(jj)%data => tfieldlist(ji)%tfield_x0d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x0d )
-    allocate(   tfieldlist(ji)%tfield_x0d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x0d(jj)%data => tfield_save_x0d(jj)%data
-      tfield_save_x0d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x0d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x0d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x1d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x1d(jj)%data => tfieldlist(ji)%tfield_x1d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x1d )
-    allocate(   tfieldlist(ji)%tfield_x1d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x1d(jj)%data => tfield_save_x1d(jj)%data
-      tfield_save_x1d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x1d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x1d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x2d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x2d(jj)%data => tfieldlist(ji)%tfield_x2d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x2d )
-    allocate(   tfieldlist(ji)%tfield_x2d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x2d(jj)%data => tfield_save_x2d(jj)%data
-      tfield_save_x2d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x2d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x2d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x3d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x3d(jj)%data => tfieldlist(ji)%tfield_x3d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x3d )
-    allocate(   tfieldlist(ji)%tfield_x3d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x3d(jj)%data => tfield_save_x3d(jj)%data
-      tfield_save_x3d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x3d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x3d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x4d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x4d(jj)%data => tfieldlist(ji)%tfield_x4d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x4d )
-    allocate(   tfieldlist(ji)%tfield_x4d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x4d(jj)%data => tfield_save_x4d(jj)%data
-      tfield_save_x4d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x4d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x4d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x5d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x5d(jj)%data => tfieldlist(ji)%tfield_x5d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x5d )
-    allocate(   tfieldlist(ji)%tfield_x5d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x5d(jj)%data => tfield_save_x5d(jj)%data
-      tfield_save_x5d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x5d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x5d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_x6d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_x6d(jj)%data => tfieldlist(ji)%tfield_x6d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_x6d )
-    allocate(   tfieldlist(ji)%tfield_x6d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_x6d(jj)%data => tfield_save_x6d(jj)%data
-      tfield_save_x6d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_x6d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_x6d(jj)%data => null()
-      end if
-    end do
-  end if
-
-  if ( allocated( tfieldlist(ji)%tfield_t0d ) ) then
-    !Save existing pointers to temporary structure
-    do jj = 1, nmodel_allocated
-      tfield_save_t0d(jj)%data => tfieldlist(ji)%tfield_t0d(jj)%data
-    end do
-    !Reallocate
-    deallocate( tfieldlist(ji)%tfield_t0d )
-    allocate(   tfieldlist(ji)%tfield_t0d(kmodelnew) )
-    !Restore pointers
-    do jj = 1, kmodelnew
-      tfieldlist(ji)%tfield_t0d(jj)%data => tfield_save_t0d(jj)%data
-      tfield_save_t0d(jj)%data => null()
-    end do
-    !Check no used pointers if nmodel is decreazed
-    do jj = kmodelnew + 1, nmodel_allocated
-      if ( associated(tfield_save_t0d(jj)%data ) ) then
-        call Print_msg( NVERB_ERROR, 'GEN', 'Fieldlist_nmodel_resize', 'data loss due to reduction in number of models' )
-        tfield_save_t0d(jj)%data => null()
-      end if
-    end do
-  end if
-
-end do
-
-nmodel_allocated = kmodelnew
-
-end subroutine Fieldlist_nmodel_resize
-
 end module mode_field
diff --git a/src/MNH/ini_segn.f90 b/src/MNH/ini_segn.f90
index 590efa55c..660947da4 100644
--- a/src/MNH/ini_segn.f90
+++ b/src/MNH/ini_segn.f90
@@ -164,7 +164,7 @@ END MODULE MODI_INI_SEG_n
 !!                       07/2017   add GBLOWSNOW (V. Vionnet)
 !  P. Wautelet 07/02/2019: force TYPE to a known value for IO_File_add2list
 !  P. Wautelet 14/02/2019: remove CLUOUT/CLUOUT0 and associated variables
-!  P. Wautelet 19/06/2019: add Fieldlist_nmodel_resize subroutine + provide KMODEL to INI_FIELD_LIST when known
+!  P. Wautelet 19/06/2019: provide KMODEL to INI_FIELD_LIST when known
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -181,7 +181,7 @@ USE MODD_PARAM_n,          ONLY: CSURF
 USE MODD_PARAMETERS
 USE MODD_REF,              ONLY: LBOUSS
 !
-use mode_field,            only: Fieldlist_nmodel_resize, Ini_field_list, Ini_field_scalars
+use mode_field,            only: Ini_field_list, Ini_field_scalars
 USE MODE_IO_FIELD_READ,    only: IO_Field_read
 USE MODE_IO_FILE,          ONLY: IO_File_close, IO_File_open
 USE MODE_IO,               only: IO_Config_set
@@ -457,10 +457,6 @@ CALL READ_EXSEG_n(KMI,TZFILE_DES,YCONF,GFLAT,GUSERV,GUSERC,                 &
                 YTURB,YTOM,GRMC01,YRAD,YDCONV,YSCONV,YCLOUD,YELEC,YEQNSYS,  &
                 PTSTEP_ALL,CSTORAGE_TYPE,CINIFILEPGD_n                      )
 !
-if ( cprogram == 'MESONH' .and. kmi == 1 ) then !Do this only once
-  call Fieldlist_nmodel_resize(NMODEL)
-end if
-!
 IF (CPROGRAM=='SPAWN ' .OR. CPROGRAM=='DIAG  ' .OR. CPROGRAM=='SPEC  '      &
      .OR. CPROGRAM=='REAL  ') THEN
   CINIFILE_n    = YINIFILE
-- 
GitLab