diff --git a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
index 4ad2b0866ff78de3f94f55658457549b4e66725b..4e467082d9923068b982c5a07f8734fdce300d78 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
@@ -391,7 +391,8 @@ subroutine IO_Field_create( tpfile, tpfield )
 #ifdef MNH_IOCDF4
           ! Write the variable attributes in the non-split file
           if ( tpfile%nmaster_rank==isp .and. gnc4 ) &
-            call IO_Field_header_split_write_nc4( tpfile, tzfield, tpfile%tncdims%tdims(tzfield%ndimlist(3))%nlen )
+            call IO_Field_header_split_write_nc4( tpfile, tzfield, &
+                                                  Int( tpfile%tncdims%tdims(tzfield%ndimlist(3))%nlen, kind = Kind( 1 ) ) )
         end if
 #endif
 
diff --git a/src/LIB/SURCOUCHE/src/mode_io_file_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_file_nc4.f90
index d2b3b5ab2311cb709fb78e0b05cc682dc200cfea..5fc23539af2b79f2eb7c989229da81b008eeab36 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_file_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_file_nc4.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2018-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2018-2021 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -70,8 +70,8 @@ end subroutine IO_File_create_nc4
 subroutine IO_File_close_nc4(tpfile,kstatus)
   use mode_io_tools_nc4, only: IO_Iocdf_dealloc_nc4
 
-  type(tfiledata),                intent(inout) :: tpfile
-  integer(kind=CDFINT), optional, intent(out)   :: kstatus
+  type(tfiledata),           intent(inout) :: tpfile
+  integer,         optional, intent(out)   :: kstatus
 
   integer(kind=CDFINT) :: istatus
 
diff --git a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
index 544dc32ce55ca53e12e8286519156f196e225f6b..f6d21f935b2095cfd24eed2a48e0a08a71839510 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_tools_nc4.f90
@@ -121,7 +121,7 @@ IF (IGRID==0) THEN
         ILEN = 1
       END IF
     CASE (1)
-      call IO_Dim_find_create_nc4( tpfile, klen, iidx )
+      call IO_Dim_find_create_nc4( tpfile, Int( klen, kind = CDFINT ), iidx )
       tpdims(1) = tpfile%tncdims%tdims(iidx)
       ilen = tpdims(1)%nlen
     CASE DEFAULT
@@ -170,7 +170,7 @@ ELSE
       ELSE IF ( YDIR == 'ZZ' ) THEN
         tpdims(1) = tpfile%tncdims%tdims( NMNHDIM_ARAKAWA(igrid,3) )
       ELSE IF (JI==TPFIELD%NDIMS) THEN !Guess last dimension
-        call IO_Dim_find_create_nc4( tpfile, klen, iidx )
+        call IO_Dim_find_create_nc4( tpfile, Int( klen, kind = CDFINT ), iidx )
         tpdims(1) = tpfile%tncdims%tdims(iidx)
       END IF
       ilen = tpdims(1)%nlen
@@ -326,7 +326,7 @@ if ( Trim( yprogram ) /= 'PGD' .and. Trim( yprogram ) /= 'NESPGD' .and. Trim( yp
   call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL,   'level',   IKU )
   call IO_Add_dim_nc4( tpfile, NMNHDIM_LEVEL_W, 'level_w', IKU )
   if ( tpfile%ctype /= 'MNHDIACHRONIC' ) &
-    call IO_Add_dim_nc4( tpfile, NMNHDIM_TIME, 'time', NF90_UNLIMITED )
+    call IO_Add_dim_nc4( tpfile, NMNHDIM_TIME, 'time', Int( NF90_UNLIMITED, kind = Kind(1) ) )
 end if
 
 if ( tpfile%ctype == 'MNHDIACHRONIC' .or. ( lpack .and. l2d ) ) then
@@ -638,7 +638,7 @@ subroutine IO_Dim_find_create_nc4( tpfile, klen, kidx, hdimname)
 use modd_netcdf, only: tdimnc
 
 type(tfiledata),            intent(in) :: tpfile
-integer,       intent(in) :: klen
+integer(kind=CDFINT),       intent(in) :: klen
 CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: HDIMNAME
 integer, intent(out) :: kidx !Position of the dimension in the dimension array
 
@@ -686,9 +686,9 @@ if ( kidx == - 1 ) then
     Write( ysuffix, '( i0 )' ) klen
     tzncdims(inewsize)%cname = 'size' // Trim( ysuffix )
   end if
-  tzncdims(inewsize)%nlen = Int( klen, kind = CDFINT )
+  tzncdims(inewsize)%nlen = klen
 
-  istatus = NF90_DEF_DIM( tpfile%nncid, tzncdims(inewsize)%cname, Int( klen, kind = CDFINT ), tzncdims(inewsize)%nid )
+  istatus = NF90_DEF_DIM( tpfile%nncid, tzncdims(inewsize)%cname, klen, tzncdims(inewsize)%nid )
   if ( istatus /= NF90_NOERR ) &
     call IO_Err_handle_nc4( istatus, 'IO_Dim_find_create_nc4', 'NF90_DEF_DIM', Trim( tzncdims(inewsize)%cname) )
 
diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
index 497aca4aa476ee02d6fb6adbe6e22e01320e3b0c..a52005298762aa03c0acdd382f424a9a9d0b7a37 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
@@ -757,7 +757,7 @@ if ( tpfield%cmnhname == 'JMAX' .and. tpfile%tncdims%tdims(NMNHDIM_NJ)%nid == -1
 end if
 #endif
 if ( tpfield%cmnhname == 'KMAX' .and. tpfile%tncdims%tdims(NMNHDIM_LEVEL)%nid == -1 ) then
-  call IO_Dim_find_create_nc4( tpfile, kfield + 2 * JPVEXT, iidx, 'Z' )
+  call IO_Dim_find_create_nc4( tpfile, Int( kfield + 2 * JPVEXT, kind = CDFINT ), iidx, 'Z' )
 end if
 
 END SUBROUTINE IO_Field_write_nc4_N0
@@ -998,7 +998,7 @@ KRESP = 0
 ILEN  = LEN(HFIELD)
 ISIZE = SIZE(HFIELD)
 
-call IO_Field_create_nc4( tpfile, tpfield, kshape = [ ilen, isize ], kvarid = ivarid, oisempty = gisempty )
+call IO_Field_create_nc4( tpfile, tpfield, kshape = Int ([ ilen, isize ], kind = Kind( 1 ) ), kvarid = ivarid, oisempty = gisempty )
 
 ! Write the data
 if ( .not. gisempty ) then
@@ -1154,7 +1154,7 @@ end if
 ! Write the data
 if ( Size( pfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:), start = istarts(:), count = Shape( pfield ) )
+  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:), start = istarts(:), count = Int( Shape( pfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_X1', 'NF90_PUT_VAR', Trim( tpfield%cmnhname ), kresp )
 end if
@@ -1198,7 +1198,7 @@ end if
 ! Write the data
 if ( Size( pfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, pfield(:,:), start = istarts(:), count = Shape( pfield ) )
+  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, pfield(:,:), start = istarts(:), count = Int( Shape( pfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_X2', 'NF90_PUT_VAR', Trim( tzfield%cmnhname ), kresp )
 end if
@@ -1237,7 +1237,7 @@ end if
 ! Write the data
 if ( Size( pfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:,:,:), start = istarts(:), count = Shape( pfield ) )
+  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:,:,:), start = istarts(:), count = Int( Shape( pfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_X3', 'NF90_PUT_VAR', Trim( tpfield%cmnhname ), kresp )
 end if
@@ -1274,7 +1274,7 @@ end if
 ! Write the data
 if ( Size( pfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:,:,:,:), start = istarts(:), count = Shape( pfield ) )
+  istatus = NF90_PUT_VAR( tpfile%nncid, ivarid, pfield(:,:,:,:), start = istarts(:), count = Int( Shape( pfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_X4', 'NF90_PUT_VAR', Trim( tpfield%cmnhname ), kresp )
 end if
@@ -1318,7 +1318,7 @@ end if
 ! Write the data
 if ( Size( kfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:), start = istarts(:), count = Shape( kfield ) )
+  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:), start = istarts(:), count = Int( Shape( kfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_N2', 'NF90_PUT_VAR', Trim( tzfield%cmnhname ), kresp )
 end if
@@ -1364,7 +1364,7 @@ end if
 ! Write the data
 if ( Size( kfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:,:), start = istarts(:), count = Shape( kfield ) )
+  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:,:), start = istarts(:), count = Int( Shape( kfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_N3', 'NF90_PUT_VAR', Trim( tzfield%cmnhname ), kresp )
 end if
@@ -1410,7 +1410,7 @@ end if
 ! Write the data
 if ( Size( kfield ) > 0 ) then
   istarts(:) = koffset(:) + 1
-  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:,:,:), start = istarts(:), count = Shape( kfield ) )
+  istatus = NF90_PUT_VAR( tzfile%nncid, ivarid, kfield(:,:,:,:), start = istarts(:), count = Int( Shape( kfield ), kind = CDFINT ) )
   if (istatus /= NF90_NOERR) &
     call IO_Err_handle_nc4( istatus, 'IO_Field_partial_write_nc4_N4', 'NF90_PUT_VAR', Trim( tzfield%cmnhname ), kresp )
 end if
diff --git a/src/MNH/read_chem_data_netcdf_case.f90 b/src/MNH/read_chem_data_netcdf_case.f90
index faef2f0c5f4b090217d07037f93ecae55c76d6b8..a33a405bcb9b36950f8043001d4eaf173e0c3a78 100644
--- a/src/MNH/read_chem_data_netcdf_case.f90
+++ b/src/MNH/read_chem_data_netcdf_case.f90
@@ -192,12 +192,13 @@ TYPE(TFILEDATA),POINTER                       :: TZFILE
 ! For netcdf 
 !
 CHARACTER(LEN=40)                     :: yrecname
+integer              :: IKILEN
 integer(kind=CDFINT) :: istatus, incid, ivarid
 integer(kind=CDFINT) :: ilat_varid, ilon_varid, ilev_varid, itime_varid
 integer(kind=CDFINT) :: ihyam_varid, ihybm_varid, ip0_varid, it_varid, iq_varid, ips_varid
 integer(kind=CDFINT) :: irecid, ilatid, ilonid, ilevid, itimeid
 integer(kind=CDFINT) :: ilatlen, ilonlen, ilevlen, inrecs, itimelen
-integer(kind=CDFINT) :: itimeindex, IKILEN
+integer(kind=CDFINT) :: itimeindex
 INTEGER, DIMENSION(:), ALLOCATABLE    :: ikinlo
 INTEGER(kind=CDFINT), DIMENSION(:), ALLOCATABLE :: icount3d, istart3d
 INTEGER(kind=CDFINT), DIMENSION(:), ALLOCATABLE :: icount2d, istart2d
diff --git a/src/MNH/write_diachro.f90 b/src/MNH/write_diachro.f90
index 77c2c8eb61d7c7fa4e4f7c24ed161c6582b756c1..485909a62c4103ad9b3ada8e0f027453d1e58e45 100644
--- a/src/MNH/write_diachro.f90
+++ b/src/MNH/write_diachro.f90
@@ -977,7 +977,7 @@ select case ( idims )
       !Correspond to FLYER_DIACHRO
       !Create local time dimension
       if ( isp == tzfile%nmaster_rank) then
-        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Size( pvar, 4), idimid )
+        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
         if ( istatus /= NF90_NOERR ) &
           call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
       end if
@@ -1095,7 +1095,7 @@ select case ( idims )
       !Correspond to FLYER_DIACHRO
       !Create local time dimension
       if ( isp == tzfile%nmaster_rank) then
-        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Size( pvar, 4), idimid )
+        istatus = NF90_DEF_DIM( igrpid, 'time_flyer', Int( Size( pvar, 4), kind = CDFINT ), idimid )
         if ( istatus /= NF90_NOERR ) &
           call IO_Err_handle_nc4( istatus, 'Write_diachro_nc4', 'NF90_DEF_DIM', Trim( tpfields(1)%cmnhname ) )
       end if