Skip to content
Snippets Groups Projects
Commit 30b22f42 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 29/01/2019: SURFEX: bug corrections + missing zero-size allocations...

Philippe 29/01/2019: SURFEX: bug corrections + missing zero-size allocations (detected with NAG compiler)
parent 77ee6c7a
No related branches found
No related tags found
No related merge requests found
!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC Copyright 2003-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 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. !SFX_LIC for details. version 1.
! ################## ! ##################
MODULE MODD_PGD_GRID MODULE MODD_PGD_GRID
...@@ -17,7 +17,7 @@ ...@@ -17,7 +17,7 @@
!! REFERENCE !! REFERENCE
!! --------- !! ---------
!! !!
!! !!
!! AUTHOR !! AUTHOR
!! ------ !! ------
!! V. Masson *Meteo France* !! V. Masson *Meteo France*
...@@ -25,6 +25,7 @@ ...@@ -25,6 +25,7 @@
!! MODIFICATIONS !! MODIFICATIONS
!! ------------- !! -------------
!! Original 10/2003 !! Original 10/2003
!! P. Wautelet 01/2019: nullify XGRID_PAR at declaration
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
IMPLICIT NONE IMPLICIT NONE
...@@ -35,7 +36,7 @@ IMPLICIT NONE ...@@ -35,7 +36,7 @@ IMPLICIT NONE
CHARACTER(LEN=10) :: CGRID ! type of grid CHARACTER(LEN=10) :: CGRID ! type of grid
INTEGER :: NL ! number of points of the surface fields INTEGER :: NL ! number of points of the surface fields
LOGICAL, DIMENSION(720,360) :: LLATLONMASK ! mask where data are to be read LOGICAL, DIMENSION(720,360) :: LLATLONMASK ! mask where data are to be read
REAL, POINTER, DIMENSION(:) :: XGRID_PAR ! lits of parameters used to define the grid REAL, POINTER, DIMENSION(:) :: XGRID_PAR => NULL() ! list of parameters used to define the grid
INTEGER :: NGRID_PAR ! size of XGRID_PAR INTEGER :: NGRID_PAR ! size of XGRID_PAR
REAL :: XMESHLENGTH ! average mesh length/width (decimal degre) REAL :: XMESHLENGTH ! average mesh length/width (decimal degre)
! !
......
!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC Copyright 2004-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 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. !SFX_LIC for details. version 1.
!################## !##################
MODULE MODN_ISBA_n MODULE MODN_ISBA_n
...@@ -27,10 +27,11 @@ MODULE MODN_ISBA_n ...@@ -27,10 +27,11 @@ MODULE MODN_ISBA_n
!! !!
!! MODIFICATIONS !! MODIFICATIONS
!! ------------- !! -------------
!! Original 01/2004 !! Original 01/2004
!! Modified 08/2009 by B. Decharme : LSURF_BUDGETC for all tiles !! Modified 08/2009 by B. Decharme : LSURF_BUDGETC for all tiles
!! Modified by A.L. Gibelin, 04/2009: add carbon spinup !! Modified by A.L. Gibelin, 04/2009: add carbon spinup
!! P. Tulet & M. Leriche 06/2017 : coupling megan online !! P. Tulet & M. Leriche 06/2017 : coupling megan online
!! P. Wautelet 01/2019: initialize XDROUGHT, XDAILYPAR, XDAILYTEMP, XMODPREC to prevent not initialized errors later on
!! !!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
...@@ -38,8 +39,9 @@ MODULE MODN_ISBA_n ...@@ -38,8 +39,9 @@ MODULE MODN_ISBA_n
! ------------ ! ------------
! !
! !
USE YOMHOOK ,ONLY : LHOOK, DR_HOOK USE MODD_SURF_PAR, ONLY : XUNDEF
USE PARKIND1 ,ONLY : JPRB USE YOMHOOK , ONLY : LHOOK, DR_HOOK
USE PARKIND1 , ONLY : JPRB
! !
IMPLICIT NONE IMPLICIT NONE
! !
...@@ -90,10 +92,10 @@ LOGICAL :: LSURF_VARS ...@@ -90,10 +92,10 @@ LOGICAL :: LSURF_VARS
LOGICAL :: LCH_BIO_FLUX LOGICAL :: LCH_BIO_FLUX
LOGICAL :: LSOILNOX LOGICAL :: LSOILNOX
LOGICAL :: LCH_NO_FLUX LOGICAL :: LCH_NO_FLUX
REAL :: XDROUGHT REAL :: XDROUGHT = XUNDEF
REAL :: XDAILYPAR REAL :: XDAILYPAR = XUNDEF
REAL :: XDAILYTEMP REAL :: XDAILYTEMP = XUNDEF
REAL :: XMODPREC REAL :: XMODPREC = XUNDEF
LOGICAL :: LGLACIER LOGICAL :: LGLACIER
LOGICAL :: LVEGUPD LOGICAL :: LVEGUPD
LOGICAL :: LNITRO_DILU LOGICAL :: LNITRO_DILU
......
!SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !SFX_LIC Copyright 2003-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 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. !SFX_LIC for details. version 1.
! ######### ! #########
SUBROUTINE WRITESURF_PGD_ISBA_PAR_n (HSELECT, DTV, HPROGRAM) SUBROUTINE WRITESURF_PGD_ISBA_PAR_n (HSELECT, DTV, HPROGRAM)
...@@ -35,6 +35,7 @@ ...@@ -35,6 +35,7 @@
!! Original 01/2003 !! Original 01/2003
!! P. Le Moigne 12/2004 : add type of photosynthesis !! P. Le Moigne 12/2004 : add type of photosynthesis
!! P. Samuelsson 10/2014: MEB !! P. Samuelsson 10/2014: MEB
!! P. Wautelet 01/2019: bug: write L_STRESS only if it exists
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
...@@ -499,6 +500,7 @@ DO JV=1,DTV%NVEGTYPE ...@@ -499,6 +500,7 @@ DO JV=1,DTV%NVEGTYPE
ENDIF ENDIF
ENDDO ENDDO
! !
IF (ASSOCIATED(DTV%LPAR_STRESS)) THEN
YRECFM='L_STRESS' YRECFM='L_STRESS'
YCOMMENT=YRECFM YCOMMENT=YRECFM
CALL WRITE_SURF(HSELECT,HPROGRAM,YRECFM,DTV%LDATA_STRESS,IRESP,HCOMMENT=YCOMMENT,HDIR='-') CALL WRITE_SURF(HSELECT,HPROGRAM,YRECFM,DTV%LDATA_STRESS,IRESP,HCOMMENT=YCOMMENT,HDIR='-')
...@@ -513,6 +515,7 @@ DO JV=1,DTV%NVEGTYPE ...@@ -513,6 +515,7 @@ DO JV=1,DTV%NVEGTYPE
ENDIF ENDIF
ENDDO ENDDO
DEALLOCATE(ZWORK) DEALLOCATE(ZWORK)
END IF
! !
YRECFM='L_H_TREE' YRECFM='L_H_TREE'
YCOMMENT=YRECFM YCOMMENT=YRECFM
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment