diff --git a/src/SURFEX/modd_netcdf_sfx.F90 b/src/SURFEX/modd_netcdf_sfx.F90 new file mode 100644 index 0000000000000000000000000000000000000000..7215606437e702f7322bc2b918df8e8c026e63e1 --- /dev/null +++ b/src/SURFEX/modd_netcdf_sfx.F90 @@ -0,0 +1,18 @@ +!SFX_LIC Copyright 2019-2019 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC for details. version 1. +! Author: P. Wautelet 18/09/2019 +module modd_netcdf_sfx + +#ifdef SFX_MNH +use modd_netcdf, only: IDCDF_KIND +#endif + +implicit none + +#ifndef SFX_MNH +integer, parameter :: IDCDF_KIND = selected_int_kind( 8 ) +#endif + +end module modd_netcdf_sfx diff --git a/src/SURFEX/modd_snow_metamo.F90 b/src/SURFEX/modd_snow_metamo.F90 index e48dd6ccda5de27a939527f451f2bf44d4dd2826..bde590cfeaf624729dcb4df92da4d226d44b9ee0 100644 --- a/src/SURFEX/modd_snow_metamo.F90 +++ b/src/SURFEX/modd_snow_metamo.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2008-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. ! ajoutEB ! correction de l'erreur interversion de XVTANG2 et XVTANG3 @@ -31,11 +31,14 @@ !! MODIFICATIONS !! ------------- !! Original 02/2008 +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! +use modd_netcdf_sfx, only: IDCDF_KIND +! IMPLICIT NONE ! !------------------------------------------------------------------------------- @@ -138,11 +141,11 @@ REAL, PARAMETER :: XVTELV1 = 0.005 ! INTEGER,PARAMETER :: NVDENT1 = 3 ! -INTEGER :: NVARDIMS !number of dimensions of netcdf input variable -INTEGER :: NLENDIM1,NLENDIM2,NLENDIM3 -INTEGER :: NID_VAR ! Netcdf IDs for variable +INTEGER(kind=IDCDF_KIND) :: NVARDIMS !number of dimensions of netcdf input variable +INTEGER(kind=IDCDF_KIND) :: NLENDIM1,NLENDIM2,NLENDIM3 +INTEGER(kind=IDCDF_KIND) :: NID_VAR ! Netcdf IDs for variable ! -INTEGER :: NID_FILE +INTEGER(kind=IDCDF_KIND) :: NID_FILE REAL, DIMENSION(:,:,:), POINTER :: XDRDT0,XTAU,XKAPPA ! field read ! END MODULE MODD_SNOW_METAMO diff --git a/src/SURFEX/mode_read_cdf.F90 b/src/SURFEX/mode_read_cdf.F90 index ce5e4a05a1f722e1f6101cb4fa8b8a658556b76e..eeb2486742dd8bcd218e48313b5977dc1dd725e4 100644 --- a/src/SURFEX/mode_read_cdf.F90 +++ b/src/SURFEX/mode_read_cdf.F90 @@ -1,10 +1,13 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 1994-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. +! Modifications: +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) MODULE MODE_READ_CDF !=================================================================== ! +use modd_netcdf_sfx, only: IDCDF_KIND ! USE MODI_ABOR1_SFX ! @@ -20,8 +23,8 @@ CONTAINS USE NETCDF ! IMPLICIT NONE -INTEGER, INTENT(IN) :: status - CHARACTER(*), INTENT(IN) :: line +INTEGER(kind=IDCDF_KIND), INTENT(IN) :: status + CHARACTER(*), INTENT(IN) :: line REAL(KIND=JPRB) :: ZHOOK_HANDLE ! ! @@ -41,19 +44,20 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: KCDF_ID !netcdf file identifiant -INTEGER,INTENT(IN) :: IDVAR !variable to read identifiant -REAL, INTENT(OUT) :: PMISSVALUE !undefined value -REAL,DIMENSION(:),INTENT(OUT) :: PVALU1D !value array +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: KCDF_ID !netcdf file identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: IDVAR !variable to read identifiant +REAL, INTENT(OUT) :: PMISSVALUE !undefined value +REAL,DIMENSION(:), INTENT(OUT) :: PVALU1D !value array ! -integer :: status +integer, parameter :: NDIMS=1 +! +integer(kind=IDCDF_KIND) :: status character(len=80) :: HACTION -integer,save :: NDIMS=1 -integer :: KVARTYPE -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) :: KVARTYPE +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM -integer :: JLOOP -integer :: NGATTS +integer(kind=IDCDF_KIND) :: JLOOP +integer(kind=IDCDF_KIND) :: NGATTS character(len=80),DIMENSION(:),ALLOCATABLE :: HNAME REAL,DIMENSION(:),ALLOCATABLE :: ZVALU1D !value array REAL(KIND=JPRB) :: ZHOOK_HANDLE @@ -132,21 +136,22 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: KCDF_ID !netcdf file identifiant -INTEGER,INTENT(IN) :: IDVAR !variable to read identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: KCDF_ID !netcdf file identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: IDVAR !variable to read identifiant REAL,DIMENSION(:),INTENT(OUT) :: PDIM1,PDIM2 !dimensions for PVALU2D array CHARACTER(len=80),INTENT(OUT) :: HDIM1NAME,HDIM2NAME !dimensions names REAL, INTENT(OUT) :: PMISSVALUE REAL,DIMENSION(:,:),INTENT(OUT) :: PVALU2D !value array ! -integer :: status +integer, parameter :: NDIMS=2 +! +integer(kind=IDCDF_KIND) :: status character(len=80) :: HACTION -integer,save :: NDIMS=2 -integer :: KVARTYPE -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) :: KVARTYPE +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM -integer :: JLOOP -integer :: NGATTS +integer(kind=IDCDF_KIND) :: JLOOP +integer(kind=IDCDF_KIND) :: NGATTS character(len=80),DIMENSION(:),ALLOCATABLE :: HNAME real :: ZMISS1,ZMISS2 REAL,DIMENSION(:,:),ALLOCATABLE :: ZVALU2D !value array @@ -235,18 +240,19 @@ IMPLICIT NONE REAL, DIMENSION(:), INTENT(OUT) :: PLON,PLAT ! Longitudes/latitudes innetcdf file REAL, DIMENSION(:), INTENT(OUT) :: PVAL ! value to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: VARNAME -integer ::JLOOP1,JDIM1,JDIM2,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -integer ::NLEN -integer,dimension(1) :: IDIMID -integer,DIMENSION(1:2) :: NLEN2D,IDIMID2D -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) ::JLOOP1 +integer ::JDIM1,JDIM2,JLOOP +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +integer(kind=IDCDF_KIND) ::NLEN +integer(kind=IDCDF_KIND),dimension(1) :: IDIMID +integer(kind=IDCDF_KIND),DIMENSION(1:2) :: NLEN2D,IDIMID2D +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM real,DIMENSION(:),ALLOCATABLE :: ZVALU real,DIMENSION(:,:),ALLOCATABLE :: ZVALU2D @@ -430,18 +436,18 @@ IMPLICIT NONE ! CHARACTER(LEN=28), INTENT(IN) :: HFILENAME ! Name of the field file. CHARACTER(LEN=28), INTENT(IN) :: HNCVARNAME ! Name of variable to read in netcdf file -INTEGER, INTENT(OUT):: KDIM ! value of dimension to get +INTEGER(kind=IDCDF_KIND), INTENT(OUT):: KDIM ! value of dimension to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: VARNAME -integer ::JLOOP1,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -integer, dimension(1) :: NDIMID -integer,DIMENSION(2) ::NLEN2D, NDIMID2D +integer(kind=IDCDF_KIND) ::JLOOP1,JLOOP +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +integer(kind=IDCDF_KIND), dimension(1) :: NDIMID +integer(kind=IDCDF_KIND),DIMENSION(2) ::NLEN2D, NDIMID2D REAL(KIND=JPRB) :: ZHOOK_HANDLE ! ! diff --git a/src/SURFEX/mode_read_grib.F90 b/src/SURFEX/mode_read_grib.F90 index ddd50d15ea3a3397107ac71dea73282a5edd4b19..ec71d31314156d270939ae14202ce729473420d3 100644 --- a/src/SURFEX/mode_read_grib.F90 +++ b/src/SURFEX/mode_read_grib.F90 @@ -1,7 +1,11 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 1994-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. +!------------------------------------------------------------------- +! Modifications: +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) +!------------------------------------------------------------------- ! ##################### MODULE MODE_READ_GRIB ! ##################### @@ -694,7 +698,7 @@ INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing REAL, DIMENSION(:), INTENT(IN) :: PMASK ! grib land mask REAL, DIMENSION(:), POINTER :: PSST ! ! -INTEGER :: IRET +INTEGER(kind=kindOfInt) :: IRET REAL(KIND=JPRB) :: ZHOOK_HANDLE !------------------------------------------------------------------- IF (LHOOK) CALL DR_HOOK('MODE_READ_GRIB:READ_GRIB_SST',0,ZHOOK_HANDLE) @@ -732,7 +736,7 @@ INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing REAL, DIMENSION(:), INTENT(IN) :: PMASK ! grib land mask REAL, DIMENSION(:), POINTER :: PTS ! ! -INTEGER :: IRET +INTEGER(kind=kindOfInt) :: IRET REAL(KIND=JPRB) :: ZHOOK_HANDLE !------------------------------------------------------------------- IF (LHOOK) CALL DR_HOOK('MODE_READ_GRIB:READ_GRIB_TSWATER',0,ZHOOK_HANDLE) diff --git a/src/SURFEX/mode_read_netcdf_mercator.F90 b/src/SURFEX/mode_read_netcdf_mercator.F90 index ad51a19ab58e80f12d7665714cf91ada168f0a3a..70d05dfc92f91be6290313d028b99633a6232b6e 100644 --- a/src/SURFEX/mode_read_netcdf_mercator.F90 +++ b/src/SURFEX/mode_read_netcdf_mercator.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 1994-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. !! !! Modified 09/2013 : S. Senesi : adapt READ_NETCDF_SST to read 2D fields other than SST @@ -10,9 +10,12 @@ MODULE MODE_READ_NETCDF_MERCATOR !! Modified 03/2014 : M.N. Bouin ! possibility of wave parameters !! ! from external source !! ! + correction of 2 bugs +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !------------------------------------------------------------------------------- ! ! +use modd_netcdf_sfx, only: IDCDF_KIND +! USE MODI_ABOR1_SFX ! USE YOMHOOK ,ONLY : LHOOK, DR_HOOK @@ -27,7 +30,7 @@ CONTAINS USE NETCDF ! IMPLICIT NONE -INTEGER, INTENT(IN) :: status +INTEGER(kind=IDCDF_KIND), INTENT(IN) :: status CHARACTER(LEN=80), INTENT(IN) :: line REAL(KIND=JPRB) :: ZHOOK_HANDLE ! @@ -48,20 +51,20 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: KCDF_ID !netcdf file identifiant -INTEGER,INTENT(IN) :: IDVAR !variable to read identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: KCDF_ID !netcdf file identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: IDVAR !variable to read identifiant REAL, INTENT(OUT) :: PMISSVALUE !undefined value REAL,DIMENSION(:),INTENT(OUT) :: PVALU1D !value array ! -integer :: status +integer, parameter :: NDIMS=1 +! +integer(kind=IDCDF_KIND) :: status character(len=80) :: HACTION -integer,save :: NDIMS=1 -integer :: KVARTYPE -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) :: KVARTYPE +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM -integer :: JLOOP -integer :: NGATTS -integer, dimension(1) :: NDIMID +integer(kind=IDCDF_KIND) :: NGATTS +integer(kind=IDCDF_KIND), dimension(1) :: NDIMID character(len=80),DIMENSION(:),ALLOCATABLE :: HNAME REAL,DIMENSION(:),ALLOCATABLE :: ZVALU1D !value array REAL(KIND=JPRB) :: ZHOOK_HANDLE @@ -122,21 +125,22 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: KCDF_ID !netcdf file identifiant -INTEGER,INTENT(IN) :: IDVAR !variable to read identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: KCDF_ID !netcdf file identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: IDVAR !variable to read identifiant REAL,DIMENSION(:),INTENT(OUT) :: PDIM1,PDIM2 !dimensions for PVALU2D array CHARACTER(len=80),INTENT(OUT) :: HDIM1NAME,HDIM2NAME !dimensions names REAL, INTENT(OUT) :: PMISSVALUE REAL,DIMENSION(:,:),INTENT(OUT) :: PVALU2D !value array ! -integer :: status +integer, parameter :: NDIMS=2 +! +integer(kind=IDCDF_KIND) :: status character(len=80) :: HACTION -integer,save :: NDIMS=2 -integer :: KVARTYPE -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) :: KVARTYPE +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM -integer :: JLOOP2, JLOOP, J1, J2 -integer :: NGATTS +integer(kind=IDCDF_KIND) :: JLOOP2, JLOOP, J1, J2 +integer(kind=IDCDF_KIND) :: NGATTS character(len=80),DIMENSION(:),ALLOCATABLE :: HNAME real :: ZMISS1,ZMISS2 real :: ZSCFA, ZOFFS @@ -249,22 +253,23 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: KCDF_ID !netcdf file identifiant -INTEGER,INTENT(IN) :: IDVAR !variable to read identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: KCDF_ID !netcdf file identifiant +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: IDVAR !variable to read identifiant REAL,DIMENSION(:),INTENT(OUT) :: PDIM1,PDIM2,PDIM3 !dimensions for PVALU2D array CHARACTER(len=80),INTENT(OUT) :: HDIM1NAME,HDIM2NAME,HDIM3NAME !dimensions names REAL, INTENT(OUT) :: PMISSVALUE REAL,DIMENSION(:,:,:),INTENT(OUT) :: PVALU3D !value array ! -integer :: status +integer, parameter :: NDIMS=3 +! +integer(kind=IDCDF_KIND) :: status character(len=80) :: HACTION -integer,save :: NDIMS=3 -integer :: KVARTYPE -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) :: KVARTYPE +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM -integer :: JLOOP2, JLOOP -integer :: J1,J2,J3 -integer :: NGATTS +integer(kind=IDCDF_KIND) :: JLOOP2, JLOOP +integer(kind=IDCDF_KIND) :: J1,J2,J3 +integer(kind=IDCDF_KIND) :: NGATTS character(len=80),DIMENSION(:),ALLOCATABLE :: HNAME real :: ZMISS1,ZMISS2,ZMISS3 real :: ZSCFA, ZOFFS @@ -384,18 +389,18 @@ IMPLICIT NONE ! CHARACTER(LEN=28), INTENT(IN) :: HFILENAME ! Name of the field file. CHARACTER(LEN=28), INTENT(IN) :: HNCVARNAME ! Name of variable to read in netcdf file -INTEGER, INTENT(OUT):: KDIM ! value of dimension to get +INTEGER(kind=IDCDF_KIND), INTENT(OUT):: KDIM ! value of dimension to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: YVARNAME -integer ::JLOOP1,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -INTEGER, DIMENSION(1) :: NDIMID -integer,DIMENSION(2) ::NLEN2D, NDIMID2D +integer(kind=IDCDF_KIND) ::JLOOP1,JLOOP +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +INTEGER(kind=IDCDF_KIND), DIMENSION(1) :: NDIMID +integer(kind=IDCDF_KIND),DIMENSION(2) ::NLEN2D, NDIMID2D REAL(KIND=JPRB) :: ZHOOK_HANDLE ! ! @@ -523,18 +528,18 @@ INCLUDE "mpif.h" CHARACTER(LEN=28), INTENT(IN) :: HFILENAME ! Name of the field file. CHARACTER(LEN=28), INTENT(IN) :: HNCVARNAME ! Name of variable to read in netcdf file ! -integer :: status -integer :: kcdf_id -integer :: INBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: INBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: YVARNAME -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID -integer ::JLOOP1,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::INVARDIMS -integer,DIMENSION(3) ::INDIMLEN +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID +integer(kind=IDCDF_KIND) ::JLOOP1,JLOOP +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::INVARDIMS +integer(kind=IDCDF_KIND),DIMENSION(3) ::INDIMLEN character(LEN=80),DIMENSION(3) :: NDIMNAM -integer :: IDIM +integer(kind=IDCDF_KIND) :: IDIM integer :: INLON INTEGER :: IINLA, INO real :: ZZLAMISS,ZZLOMISS @@ -767,16 +772,16 @@ IMPLICIT NONE CHARACTER(LEN=28), INTENT(IN) :: HNCVARNAME ! Name of variable to read in netcdf file REAL, DIMENSION(:), INTENT(OUT) :: PVAL ! value to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: VARNAME -integer ::JLOOP1 -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -INTEGER, DIMENSION(1) :: NDIMID -integer ::NLEN +integer(kind=IDCDF_KIND) ::JLOOP1 +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +INTEGER(kind=IDCDF_KIND), DIMENSION(1) :: NDIMID +integer(kind=IDCDF_KIND) ::NLEN real,DIMENSION(:),ALLOCATABLE :: ZVALU real :: ZMISS REAL(KIND=JPRB) :: ZHOOK_HANDLE @@ -886,18 +891,18 @@ IMPLICIT NONE REAL, DIMENSION(:), INTENT(OUT) :: PLON,PLAT ! Longitudes/latitudes in netcdf file REAL, DIMENSION(:), INTENT(OUT) :: PVAL ! value to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: VARNAME -integer ::JLOOP1,JDIM1,JDIM2,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -integer ::NLEN -integer, dimension(1) :: NDIMID -integer,DIMENSION(2) ::NLEN2D, NDIMID2D -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) ::JLOOP1,JDIM1,JDIM2,JLOOP +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +integer(kind=IDCDF_KIND) ::NLEN +integer(kind=IDCDF_KIND), dimension(1) :: NDIMID +integer(kind=IDCDF_KIND),DIMENSION(2) ::NLEN2D, NDIMID2D +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM real,DIMENSION(:),ALLOCATABLE :: ZVALU real,DIMENSION(:,:),ALLOCATABLE :: ZVALU2D @@ -1087,17 +1092,18 @@ REAL, DIMENSION(:), INTENT(OUT) :: PLON,PLAT ! Longitudes/latitudes in netcdf fi REAL, DIMENSION(:), INTENT(OUT) :: PDEP ! depth in netcdf file REAL, DIMENSION(:,:), INTENT(OUT) :: PVAL ! value to get ! -integer :: status -integer :: kcdf_id -integer :: NBVARS +integer(kind=IDCDF_KIND) :: status +integer(kind=IDCDF_KIND) :: kcdf_id +integer(kind=IDCDF_KIND) :: NBVARS character(len=80) :: HACTION character(len=80),DIMENSION(:),ALLOCATABLE :: VARNAME -integer ::JLOOP1,JDIM1,JDIM2,JDIM3,JLOOP +integer(kind=IDCDF_KIND) ::JLOOP1 +integer :: JDIM1,JDIM2,JDIM3,JLOOP !integer ::JLOOP2,JLOOP -integer ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 -integer ::NVARDIMS -integer,DIMENSION(3) ::NLEN3D -integer,DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN +integer(kind=IDCDF_KIND) ::ID_VARTOGET,ID_VARTOGET1,ID_VARTOGET2 +integer(kind=IDCDF_KIND) ::NVARDIMS +integer(kind=IDCDF_KIND),DIMENSION(3) ::NLEN3D +integer(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE :: NVARDIMID,NVARDIMLEN character(len=80),DIMENSION(:),ALLOCATABLE :: NVARDIMNAM real,DIMENSION(:,:,:),ALLOCATABLE :: ZVALU3D real :: ZMISS diff --git a/src/SURFEX/mode_snowcro_flanner.F90 b/src/SURFEX/mode_snowcro_flanner.F90 index afa89445276a1ea7d3d79c86b83dd14669b5a9d8..9ece1449a71139a6a159ef7ddf4a86b79a087497 100644 --- a/src/SURFEX/mode_snowcro_flanner.F90 +++ b/src/SURFEX/mode_snowcro_flanner.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2013-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. MODULE MODE_SNOWCRO_FLANNER @@ -24,6 +24,10 @@ MODULE MODE_SNOWCRO_FLANNER !! ------------- !! Original 01/2013 ! +! Modifications: +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) +! +use modd_netcdf_sfx, only : IDCDF_KIND USE MODD_SURFEX_OMP, ONLY : NBLOCK USE MODD_SURFEX_MPI, ONLY : NRANK, NPIO, NPROC, NCOMM ! @@ -72,7 +76,7 @@ IMPLICIT NONE !* 2. declarations of local variables ! INTEGER :: INFOMPI -INTEGER :: IERROR !error status +INTEGER(kind=IDCDF_KIND) :: IERROR !error status ! REAL(KIND=JPRB) :: ZHOOK_HANDLE ! @@ -115,14 +119,14 @@ USE NETCDF ! IMPLICIT NONE ! -INTEGER,INTENT(IN) :: ID_FILE +INTEGER(kind=IDCDF_KIND),INTENT(IN) :: ID_FILE CHARACTER(LEN=5),INTENT(IN) :: HSURF REAL, DIMENSION(:,:,:), POINTER :: PVAR ! INTEGER :: INFOMPI -INTEGER, DIMENSION(:), ALLOCATABLE :: IVARDIMSID +INTEGER(kind=IDCDF_KIND), DIMENSION(:), ALLOCATABLE :: IVARDIMSID ! -INTEGER :: IERROR !error status +INTEGER(kind=IDCDF_KIND) :: IERROR !error status ! IF (NRANK==NPIO) THEN ! Look for variable ID diff --git a/src/SURFEX/prep_isba_netcdf.F90 b/src/SURFEX/prep_isba_netcdf.F90 index c61ec8c397670cd77ad5579eb3b1ceeda601f857..6bbaf1c7cf57ff0ae672324e4b1c40c861f6b892 100644 --- a/src/SURFEX/prep_isba_netcdf.F90 +++ b/src/SURFEX/prep_isba_netcdf.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2012-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. ! ######### SUBROUTINE PREP_ISBA_NETCDF (DTCO, U, HPROGRAM,HSURF,HFILE,KLUOUT,PFIELD) @@ -26,10 +26,14 @@ SUBROUTINE PREP_ISBA_NETCDF (DTCO, U, HPROGRAM,HSURF,HFILE,KLUOUT,PFIELD) !! ------------- !! Original 04/2012 !! J.Escobar 11/2013 Add USE MODI_GET_TYPE_DIM_n +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !!------------------------------------------------------------------ ! ! ! +USE GRIB_API, ONLY : kindOfInt +! +use modd_netcdf_sfx, only: IDCDF_KIND USE MODD_DATA_COVER_n, ONLY : DATA_COVER_t USE MODD_SURF_ATM_n, ONLY : SURF_ATM_t ! @@ -50,7 +54,6 @@ USE PARKIND1 ,ONLY : JPRB USE NETCDF ! IMPLICIT NONE - ! !* 0.1 declarations of arguments ! @@ -73,14 +76,14 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZFIELD, ZFIELD0 ! field read REAL(KIND=JPRB) :: ZHOOK_HANDLE ! INTEGER :: JI, ICPT -INTEGER::IERROR !error status +INTEGER(kind=kindOfInt)::IERROR !error status INTEGER::JJ,JK,JLOOP ! loop counters INTEGER::INLAYERS ! vertical dimension length INTEGER::IL ! nature dimension length -INTEGER::ID_FILE,ID_VAR ! Netcdf IDs for file and variable -INTEGER::INVARDIMS !number of dimensions of netcdf input variable -INTEGER,DIMENSION(:),ALLOCATABLE::IVARDIMSID -INTEGER::ILENDIM,ILENDIM1,ILENDIM2 +INTEGER(kind=IDCDF_KIND)::ID_FILE,ID_VAR ! Netcdf IDs for file and variable +INTEGER(kind=IDCDF_KIND)::INVARDIMS !number of dimensions of netcdf input variable +INTEGER(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE::IVARDIMSID +INTEGER(kind=IDCDF_KIND)::ILENDIM,ILENDIM1,ILENDIM2 SELECT CASE (TRIM(HSURF)) CASE ('TG','WG','WGI') diff --git a/src/SURFEX/read_netcdf.F90 b/src/SURFEX/read_netcdf.F90 index bdd337748e285b1dd8725e6c0abf392282f98e1e..faa41334bb204fa475e1e334ae18aef8f82b9488 100644 --- a/src/SURFEX/read_netcdf.F90 +++ b/src/SURFEX/read_netcdf.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2008-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. ! ######### SUBROUTINE READ_NETCDF (UG, U, USS, & @@ -23,12 +23,14 @@ !! !! Original 01/2008 !! +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !---------------------------------------------------------------------------- ! !* 0. DECLARATION ! ----------- ! ! +use modd_netcdf_sfx, only : IDCDF_KIND USE MODD_SURF_ATM_GRID_n, ONLY : SURF_ATM_GRID_t USE MODD_SURF_ATM_n, ONLY : SURF_ATM_t USE MODD_SSO_n, ONLY : SSO_t @@ -73,7 +75,7 @@ REAL, DIMENSION(:),ALLOCATABLE :: ZLATI ! array of values extract from netcdf ! INTEGER :: ILUOUT ! output listing INTEGER :: JLOOP ! loop indice -INTEGER :: JDIMENSION ! dimensions of ZVALU,ZLAT, +INTEGER(kind=IDCDF_KIND) :: JDIMENSION ! dimensions of ZVALU,ZLAT, REAL(KIND=JPRB) :: ZHOOK_HANDLE ! and ZLON arrays !---------------------------------------------------------------------------- diff --git a/src/SURFEX/read_pgd_netcdf.F90 b/src/SURFEX/read_pgd_netcdf.F90 index a30e3b5ad8e4c858b2a6ea43e36be0e0cb5f3166..5e417d04982463d546908fd6b4c3993c123a4c61 100644 --- a/src/SURFEX/read_pgd_netcdf.F90 +++ b/src/SURFEX/read_pgd_netcdf.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2012-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. !################################################################################# SUBROUTINE READ_PGD_NETCDF (UG, U, USS, & @@ -26,13 +26,17 @@ SUBROUTINE READ_PGD_NETCDF (UG, U, USS, & !! MODIFICATIONS !! ------------- !! Original 11/2012 +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !!------------------------------------------------------------------ ! ! +use modd_netcdf_sfx, only : IDCDF_KIND USE MODD_SURF_ATM_GRID_n, ONLY : SURF_ATM_GRID_t USE MODD_SURF_ATM_n, ONLY : SURF_ATM_t USE MODD_SSO_n, ONLY : SSO_t ! +USE MODE_READ_CDF, ONLY : IDCDF_KIND + USE MODI_ABOR1_SFX USE MODI_READ_AND_SEND_MPI @@ -73,9 +77,9 @@ REAL, DIMENSION(:), ALLOCATABLE :: ZFIELD0 ! ! CHARACTER(LEN=28) :: YNCVAR ! -INTEGER::IERROR !error status -INTEGER::ID_FILE ! id of netcdf file -INTEGER::INFIELD,INLAT,INLON ! dimension lengths +INTEGER(kind=IDCDF_KIND)::IERROR !error status +INTEGER(kind=IDCDF_KIND)::ID_FILE ! id of netcdf file +INTEGER(kind=IDCDF_KIND)::INFIELD,INLAT,INLON ! dimension lengths INTEGER::ILUOUT INTEGER::JPOINT !loop counter ! @@ -175,17 +179,17 @@ USE NETCDF IMPLICIT NONE -INTEGER,INTENT(IN)::ID_FILE +INTEGER(kind=IDCDF_KIND),INTENT(IN)::ID_FILE CHARACTER(LEN=20), INTENT(IN) :: HFIELD ! name of variable REAL,DIMENSION(:),POINTER::PFIELD -INTEGER::ID_VAR ! Netcdf IDs for file and variable -INTEGER::INVARDIMS !number of dimensions of netcdf input variable -INTEGER,DIMENSION(:),ALLOCATABLE::IVARDIMSID -INTEGER::ILENDIM1,ILENDIM2 -INTEGER,INTENT(OUT)::ILENDIM -INTEGER::IERROR !error status -INTEGER::ITYPE +INTEGER(kind=IDCDF_KIND)::ID_VAR ! Netcdf IDs for file and variable +INTEGER(kind=IDCDF_KIND)::INVARDIMS !number of dimensions of netcdf input variable +INTEGER(kind=IDCDF_KIND),DIMENSION(:),ALLOCATABLE::IVARDIMSID +INTEGER(kind=IDCDF_KIND)::ILENDIM1,ILENDIM2 +INTEGER(kind=IDCDF_KIND),INTENT(OUT)::ILENDIM +INTEGER(kind=IDCDF_KIND)::IERROR !error status +INTEGER(kind=IDCDF_KIND)::ITYPE ! Look for variable ID for HFIELD IERROR=NF90_INQ_VARID(ID_FILE,TRIM(HFIELD),ID_VAR) diff --git a/src/SURFEX/read_z1d_netcdf.F90 b/src/SURFEX/read_z1d_netcdf.F90 index af433b7392ff96229cc157444ba18483b7a4522f..e60057624d151523735dfbd339b08deff7972824 100644 --- a/src/SURFEX/read_z1d_netcdf.F90 +++ b/src/SURFEX/read_z1d_netcdf.F90 @@ -1,6 +1,6 @@ -!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC Copyright 2014-2019 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence -!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt !SFX_LIC for details. version 1. ! ######### SUBROUTINE READ_Z1D_NETCDF @@ -21,12 +21,14 @@ !! !! Original 11/2014 !! initialisation of NOCKMAX,XZHOC -!! +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) +! !---------------------------------------------------------------------------- ! !* 0. DECLARATION ! ----------- ! +use modd_netcdf_sfx, only : IDCDF_KIND USE MODD_OCEAN_GRID USE MODD_SURF_PAR, ONLY : NUNDEF USE MODD_PREP_SEAFLUX, ONLY : CFILE_SEAFLX,CTYPE_SEAFLX @@ -42,7 +44,7 @@ IMPLICIT NONE ! CHARACTER (LEN=28) :: YFILENAME CHARACTER (LEN=28) :: YNCVARNAME -INTEGER :: JDIMENSION +INTEGER(kind=IDCDF_KIND) :: JDIMENSION ! !* 0.2 Declaration of local variables ! ------------------------------ diff --git a/src/SURFEX/start_lake_of.F90 b/src/SURFEX/start_lake_of.F90 index 0f08293016c79cdfd7efc516e9d71ebeb48b335a..294b8598480d71b42dfd24a59d57f8688864b17a 100644 --- a/src/SURFEX/start_lake_of.F90 +++ b/src/SURFEX/start_lake_of.F90 @@ -45,6 +45,7 @@ SUBROUTINE START_LAKE_OF(KDAY, KMONTH, PLON, PLAT, PDEPTH, & ! IN ! Modified 07/2012, P. Le Moigne : In case there's a lake but no climatic data ! associated then fill with neighbour existing data ! instead of aborting +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) !------------------------------------------------------------------------------------------------------------ ! USE MODD_DATA_LAKE, ONLY : CLAKELTA, NLONG, NLATG, XFIRSTLAT, & @@ -52,6 +53,7 @@ USE MODD_DATA_LAKE, ONLY : CLAKELTA, NLONG, NLATG, XFIRSTLAT, & XAUXT_SNOW, XAUXT_ICE, XAUXT_MNW, XAUXT_WML, XAUXT_BOT, & XAUXT_B1, XAUXCT, XAUXH_SNOW, XAUXH_ICE, XAUXH_ML, & XAUXH_B1, XAUXT_SFC +use modd_netcdf_sfx, only : IDCDF_KIND ! USE MODI_ABOR1_SFX ! @@ -62,6 +64,7 @@ USE NETCDF ! IMPLICIT NONE ! +! !* 0.1 declarations of arguments ! INTEGER, INTENT(IN) :: KDAY, & ! The day number @@ -97,7 +100,7 @@ REAL :: ZWLON, ZWLAT, ZWDEPTH ! LOGICAL :: LEXIST ! - INTEGER :: ID_LAKELTA, ID_MONTH, & ! IDs for NetCDF + INTEGER(kind=IDCDF_KIND) :: ID_LAKELTA, ID_MONTH, & ! IDs for NetCDF ID_DEC, ID_LON, ID_LAT, ID_DEPTH, & ID_T_SNOW, ID_T_ICE, ID_T_MNW, ID_T_WML, ID_T_BOT, ID_T_B1, ID_CT, & ID_H_SNOW, ID_H_ICE, ID_H_ML, ID_H_B1, ID_T_SFC @@ -105,9 +108,9 @@ LOGICAL :: LEXIST INTEGER :: ILON, ILAT ! Numbers of the "lake" grid boxes in longitude and latitude INTEGER :: IDEPTH ! Number of the lake class in depth INTEGER, DIMENSION(1) :: ILOC_DEPTH - INTEGER :: IRET - INTEGER :: IMONTHN, IDECN, ILONN, ILATN, IDEPTHN - INTEGER, DIMENSION(5) :: NINDEX + INTEGER(kind=IDCDF_KIND) :: IRET + INTEGER(kind=IDCDF_KIND) :: IMONTHN, IDECN, ILONN, ILATN, IDEPTHN + INTEGER(kind=IDCDF_KIND), DIMENSION(5) :: NINDEX REAL(KIND=JPRB) :: ZHOOK_HANDLE ! ---------------------------------------------------------------------------------------------- ! diff --git a/src/SURFEX/uncompress_field.F90 b/src/SURFEX/uncompress_field.F90 index fadc0be3f840632dfd4432c870b6173361025bb0..a3c2aa88e052868ef2453d6666253eca49c9ecb1 100644 --- a/src/SURFEX/uncompress_field.F90 +++ b/src/SURFEX/uncompress_field.F90 @@ -1,8 +1,16 @@ +!SFX_LIC Copyright 1994-2019 CNRS, Meteo-France and Universite Paul Sabatier +!SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence +!SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt +!SFX_LIC for details. version 1. +!------------------------------------------------------------------------------------------------------------ +! Modifications: +! P. Wautelet 19/09/2019: correct support of 64bit integers (MNH_INT=8) +!------------------------------------------------------------------------------------------------------------ SUBROUTINE UNCOMPRESS_FIELD(KLONG,PSEUIL,PFIELD_IN,PFIELD_OUT) IMPLICIT NONE -INTEGER*4, INTENT(IN) :: KLONG +INTEGER, INTENT(IN) :: KLONG REAL, INTENT(IN) :: PSEUIL REAL, DIMENSION(:), INTENT(IN) :: PFIELD_IN REAL, DIMENSION(:), INTENT(OUT) :: PFIELD_OUT