From b8f2502b98b71fb808d56c2a3d26c10d98611a29 Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Mon, 19 Jul 2021 13:56:21 +0200
Subject: [PATCH] Philippe 19/07/2021: fix to allow correct compilation with
 MNH_INT=8

---
 src/MNH/read_cams_data_netcdf_case.f90 | 34 +++++++++++++-------------
 src/MNH/set_rsou.f90                   |  9 ++++---
 src/MNH/write_diachro.f90              |  2 +-
 3 files changed, 23 insertions(+), 22 deletions(-)

diff --git a/src/MNH/read_cams_data_netcdf_case.f90 b/src/MNH/read_cams_data_netcdf_case.f90
index 10fea94e3..89ab3518c 100644
--- a/src/MNH/read_cams_data_netcdf_case.f90
+++ b/src/MNH/read_cams_data_netcdf_case.f90
@@ -158,6 +158,7 @@ CHARACTER(LEN=2)                   :: YPGD_TYPE     ! not used - dummy argument
 INTEGER                            :: INO           ! Number of points of the grid
 INTEGER                            :: IIU           ! Number of points along X
 INTEGER                            :: IJU           ! Number of points along Y
+integer                            :: ilatlen, ilonlen, ilevlen
 REAL, DIMENSION(:), ALLOCATABLE    :: ZLONOUT       ! mapping PGD -> Grib (lon.)
 REAL, DIMENSION(:), ALLOCATABLE    :: ZLATOUT       ! mapping PGD -> Grib (lat.)
 REAL, DIMENSION(:,:), ALLOCATABLE  :: ZXM           ! X of PGD mass points
@@ -169,13 +170,11 @@ INTEGER                           :: IMI
 ! For netcdf 
 !
 integer(kind=CDFINT) :: istatus, incid
-integer(kind=CDFINT) :: ilatlen, ilonlen, ilevlen, inrecs
 integer(kind=CDFINT) :: itimeindex
 INTEGER(kind=CDFINT)               :: ind_netcdf    ! Indice for netcdf var.
 REAL, DIMENSION(:), ALLOCATABLE       :: zlats
 REAL, DIMENSION(:), ALLOCATABLE       :: zlons 
 REAL, DIMENSION(:), ALLOCATABLE       :: zlevs 
-REAL, DIMENSION(:), ALLOCATABLE       :: ztime
 REAL, DIMENSION(:,:,:), ALLOCATABLE   :: zmmr_dust1, zmmr_dust2, zmmr_dust3
 REAL, DIMENSION(:,:,:), ALLOCATABLE   :: zmmr_seasalt1, zmmr_seasalt2, zmmr_seasalt3
 REAL, DIMENSION(:,:,:), ALLOCATABLE   :: zmmr_bc_hydrophilic, zmmr_bc_hydrophobic
@@ -251,7 +250,6 @@ CALL READ_DIM(incid,"level",ilevlen)
 ALLOCATE (zlats(ilatlen))
 ALLOCATE (zlons(ilonlen))
 ALLOCATE (zlevs(ilevlen))
-ALLOCATE (ztime(inrecs))
 ! T, Q, Ps :
 ALLOCATE (ZTMOZ(ilonlen,ilatlen,ilevlen))
 ALLOCATE (ZQMOZ(ilonlen,ilatlen,ilevlen))
@@ -541,7 +539,6 @@ DEALLOCATE (ZLONOUT)
 DEALLOCATE (zlats)
 DEALLOCATE (zlons)
 DEALLOCATE (zlevs)
-DEALLOCATE (ztime)
 ! ps, T, Q :
 DEALLOCATE (ZPSMOZ)
 DEALLOCATE (ZTMOZ)
@@ -621,17 +618,20 @@ END SUBROUTINE ARRAY_1D_TO_2D
 !       Small routine used to store a linear array into a 2 dimension array
 !
 IMPLICIT NONE
-INTEGER(kind=CDFINT),                INTENT(IN)  :: file
+INTEGER(kind=CDFINT),   INTENT(IN)  :: file
 CHARACTER(*),           INTENT(IN)  :: name
-INTEGER(kind=CDFINT),                INTENT(OUT) :: output
+INTEGER,                INTENT(OUT) :: output
 !
+INTEGER(kind=CDFINT) :: ilen
 INTEGER(kind=CDFINT) :: istatus, index
 !
 istatus = nf90_inq_dimid(file, name, index)
 if (istatus /= nf90_noerr) call handle_err(istatus)
-istatus = nf90_inquire_dimension(file, index, len=output)
+istatus = nf90_inquire_dimension(file, index, len=ilen)
 if (istatus /= nf90_noerr) call handle_err(istatus)
 !
+output = ilen
+!
 END SUBROUTINE READ_DIM
 !
 !     #############################################
@@ -641,9 +641,9 @@ END SUBROUTINE READ_DIM
 !       Small routine used to store a linear array into a 2 dimension array
 !
 IMPLICIT NONE
-INTEGER(kind=CDFINT),                INTENT(IN)  :: file
+INTEGER(kind=CDFINT),   INTENT(IN)  :: file
 CHARACTER(*),           INTENT(IN)  :: name
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size
+INTEGER,                INTENT(IN)  :: size
 REAL, DIMENSION(size),  INTENT(INOUT) :: output
 !
 INTEGER(kind=CDFINT) :: istatus, index
@@ -662,10 +662,10 @@ END SUBROUTINE READ_VAR_1D
 !       Small routine used to store a linear array into a 2 dimension array
 !
 IMPLICIT NONE
-INTEGER(kind=CDFINT),                INTENT(IN)  :: file
+INTEGER(kind=CDFINT),   INTENT(IN)  :: file
 CHARACTER(*),           INTENT(IN)  :: name
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size_lon
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size_lat
+INTEGER,                INTENT(IN)  :: size_lon
+INTEGER,                INTENT(IN)  :: size_lat
 REAL, DIMENSION(size_lon,size_lat),      INTENT(INOUT) :: output
 !
 INTEGER(kind=CDFINT) :: istatus, index
@@ -694,16 +694,16 @@ END SUBROUTINE READ_VAR_2D
 !       Small routine used to store a linear array into a 2 dimension array
 !
 IMPLICIT NONE
-INTEGER(kind=CDFINT),                INTENT(IN)  :: file
+INTEGER(kind=CDFINT),   INTENT(IN)  :: file
 CHARACTER(*),           INTENT(IN)  :: name
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size_lon
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size_lat
-INTEGER(kind=CDFINT),                INTENT(IN)  :: size_lev
+INTEGER,                INTENT(IN)  :: size_lon
+INTEGER,                INTENT(IN)  :: size_lat
+INTEGER,                INTENT(IN)  :: size_lev
 REAL, DIMENSION(size_lon,size_lat,size_lev),      INTENT(INOUT) :: output
 !
 INTEGER(kind=CDFINT) :: istatus, index
 REAL :: scale, offset
-INTEGER,DIMENSION(4) :: s, c
+INTEGER(kind=CDFINT),DIMENSION(4) :: s, c
 !
 s(:)=1
 c(1)=size_lon
diff --git a/src/MNH/set_rsou.f90 b/src/MNH/set_rsou.f90
index 23423e8b0..c0aca1504 100644
--- a/src/MNH/set_rsou.f90
+++ b/src/MNH/set_rsou.f90
@@ -391,7 +391,8 @@ REAL,DIMENSION(SIZE(XXHAT),SIZE(XYHAT),SIZE(XZHAT)) ::ZZFLUX_MX,ZZMASS_MX ! mixe
 !-------------------------------------------------------------------------------
 ! For standard ocean version, reading external files
 CHARACTER(LEN=256) :: yinfile, yinfisf ! files to be read
-INTEGER :: INZ, INLATI, INLONGI, IDX
+INTEGER :: IDX
+INTEGER(KIND=CDFINT) :: INZ, INLATI, INLONGI
 INTEGER(KIND=CDFINT) :: incid, ivarid, idimid, idimlen
 REAL, DIMENSION(:,:,:),     ALLOCATABLE :: ZOC_TEMPERATURE,ZOC_SALINITY,ZOC_U,ZOC_V
 REAL, DIMENSION(:),     ALLOCATABLE :: ZOC_DEPTH  
@@ -588,9 +589,9 @@ SELECT CASE(YKIND)
     CALL check(nf90_open(yinfile,NF90_NOWRITE,incid), "opening NC file")
     ! Reading dimensions and lengths
     CALL check( nf90_inq_dimid(incid, "depth",idimid), "getting depth  dimension id" )
-    CALL check( nf90_inquire_dimension(incid, idimid, len=INZ), "getting INZ "  )
-    CALL check( nf90_inquire_dimension(incid, 2, len=INLONGI), "getting NLONG "  )
-    CALL check( nf90_inquire_dimension(incid, 1, len=INLATI), "getting NLAT "  )
+    CALL check( nf90_inquire_dimension(incid, idimid,             len=INZ),     "getting INZ"   )
+    CALL check( nf90_inquire_dimension(incid, INT(2,KIND=CDFINT), len=INLONGI), "getting NLONG" )
+    CALL check( nf90_inquire_dimension(incid, INT(1,KIND=CDFINT), len=INLATI),  "getting NLAT"  )
 !   
     WRITE(ILUOUT,FMT=*) 'NB LEVLS READ INZ, NLONG NLAT ', INZ, INLONGI,INLATI
     ALLOCATE(ZOC_TEMPERATURE(INLATI,INLONGI,INZ),ZOC_SALINITY(INLATI,INLONGI,INZ))
diff --git a/src/MNH/write_diachro.f90 b/src/MNH/write_diachro.f90
index a1170be6f..8ad7c4538 100644
--- a/src/MNH/write_diachro.f90
+++ b/src/MNH/write_diachro.f90
@@ -818,7 +818,7 @@ 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
+logical,              dimension(0:NMAXLEVELS) :: gleveldefined ! Are the different groups/levels already defined in the netCDF file
 type(tfielddata)                              :: tzfield
 type(tfiledata)                               :: tzfile
 
-- 
GitLab