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

Philippe 07/12/2020: add CLEANLIST1D_ll subroutine + use it to correctly...

Philippe 07/12/2020: add CLEANLIST1D_ll subroutine + use it to correctly deallocate associated memory

(cherry picked from commit 2646cee7)
parent c06f8623
No related branches found
No related tags found
No related merge requests found
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 1998-2020 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 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1. !MNH_LIC for details. version 1.
...@@ -23,7 +23,7 @@ ...@@ -23,7 +23,7 @@
! !
! SUBROUTINES : ADD1DFIELD_ll, ADD2DFIELD_ll, ADD3DFIELD_ll ! SUBROUTINES : ADD1DFIELD_ll, ADD2DFIELD_ll, ADD3DFIELD_ll
! DEL1DFIELD_ll, DEL2DFIELD_ll, DEL3DFIELD_ll ! DEL1DFIELD_ll, DEL2DFIELD_ll, DEL3DFIELD_ll
! CLEANLIST_ll ! CLEANLIST_ll, CLEANLIST1D_ll
! !
!! Purpose !! Purpose
!! ------- !! -------
...@@ -55,7 +55,9 @@ ...@@ -55,7 +55,9 @@
!! Modifications !! Modifications
!! ------------- !! -------------
! Original May 19, 1998 ! Original May 19, 1998
! ! P. Wautelet 10/04/2019: replace ABORT and STOP calls by Print_msg
! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine
! P. Wautelet 07/12/2020: add CLEANLIST1D_ll subroutine
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
! Implicit arguments ! Implicit arguments
...@@ -642,6 +644,7 @@ ...@@ -642,6 +644,7 @@
! !
END SUBROUTINE DEL3DFIELD_ll END SUBROUTINE DEL3DFIELD_ll
! !
!
!! ############################### !! ###############################
SUBROUTINE CLEANLIST_ll(TPLIST) SUBROUTINE CLEANLIST_ll(TPLIST)
!! ############################### !! ###############################
...@@ -707,4 +710,31 @@ ...@@ -707,4 +710,31 @@
! !
END SUBROUTINE CLEANLIST_ll END SUBROUTINE CLEANLIST_ll
! !
!! ###############################
SUBROUTINE CLEANLIST1D_ll(TPLIST)
!! ###############################
IMPLICIT NONE
!
TYPE(LIST1D_ll), POINTER :: TPLIST ! List of fields
!
TYPE(LIST1D_ll), POINTER :: TZTEMP
!
!------------------------------------------------------------------------------
!
!* 1. Deallocate one by one the elements of TPLIST
! --------------------------------------------
!
IF (ASSOCIATED(TPLIST)) THEN
DO WHILE(ASSOCIATED(TPLIST))
TZTEMP => TPLIST
TPLIST => TPLIST%NEXT
DEALLOCATE(TZTEMP)
END DO
NULLIFY(TPLIST)
END IF
!
!------------------------------------------------------------------------------
!
END SUBROUTINE CLEANLIST1D_ll
END MODULE MODE_ARGSLIST_ll END MODULE MODE_ARGSLIST_ll
!MNH_LIC Copyright 1994-2018 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 1994-2020 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 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1. !MNH_LIC for details. version 1.
...@@ -34,6 +34,8 @@ ...@@ -34,6 +34,8 @@
!! Original 06/05/94 !! Original 06/05/94
!! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
!! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O !! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine
! P. Wautelet 07/12/2020: bugfix: deallocate correctly TZHALO1_ll
!-------------------------------------------------------------------------------- !--------------------------------------------------------------------------------
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
...@@ -203,7 +205,7 @@ PDYHAT(:) = EOSHIFT(PYHAT(:) ,1,ZBOUNDY) - PYHAT(:) ...@@ -203,7 +205,7 @@ PDYHAT(:) = EOSHIFT(PYHAT(:) ,1,ZBOUNDY) - PYHAT(:)
CALL ADD1DFIELD_ll("X",TZHALO1_ll,PDXHAT) CALL ADD1DFIELD_ll("X",TZHALO1_ll,PDXHAT)
CALL ADD1DFIELD_ll("Y",TZHALO1_ll,PDYHAT) CALL ADD1DFIELD_ll("Y",TZHALO1_ll,PDYHAT)
CALL UPDATE_1DHALO_ll(TZHALO1_ll,IINFO_ll) CALL UPDATE_1DHALO_ll(TZHALO1_ll,IINFO_ll)
DEALLOCATE(TZHALO1_ll) CALL CLEANLIST1D_ll( TZHALO1_ll )
! !
ZDZ(:,:,1:IKU-1) = PZZ(:,:,2:IKU) - PZZ(:,:,1:IKU-1) ZDZ(:,:,1:IKU-1) = PZZ(:,:,2:IKU) - PZZ(:,:,1:IKU-1)
ZDZ(:,:,IKU) = ZBOUNDZ(:,:) - PZZ(:,:,IKU) ZDZ(:,:,IKU) = ZBOUNDZ(:,:) - PZZ(:,:,IKU)
......
!MNH_LIC Copyright 1994-2018 CNRS, Meteo-France and Universite Paul Sabatier !MNH_LIC Copyright 1994-2020 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 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 version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1. !MNH_LIC for details. version 1.
...@@ -37,8 +37,9 @@ ...@@ -37,8 +37,9 @@
!! Original 24/05/94 !! Original 24/05/94
!! 05/02/15 M.Moge (LA-CNRS) !! 05/02/15 M.Moge (LA-CNRS)
!! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O !! Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
!! ! P. Wautelet 10/04/2019: replace ABORT and STOP calls by Print_msg
!! ! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine
! P. Wautelet 07/12/2020: bugfix: deallocate correctly TZHALO1_ll
!------------------------------------------------------------------------------ !------------------------------------------------------------------------------
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
...@@ -360,7 +361,7 @@ ZDZ(:,:,IKU) = ZDZ(:,:,IKU-1) ...@@ -360,7 +361,7 @@ ZDZ(:,:,IKU) = ZDZ(:,:,IKU-1)
CALL ADD1DFIELD_ll("X",TZHALO1_ll,PDXHAT) CALL ADD1DFIELD_ll("X",TZHALO1_ll,PDXHAT)
CALL ADD1DFIELD_ll("Y",TZHALO1_ll,PDYHAT) CALL ADD1DFIELD_ll("Y",TZHALO1_ll,PDYHAT)
CALL UPDATE_1DHALO_ll(TZHALO1_ll,IINFO_ll) CALL UPDATE_1DHALO_ll(TZHALO1_ll,IINFO_ll)
DEALLOCATE(TZHALO1_ll) call CLEANLIST1D_ll( TZHALO1_ll )
CALL MPPDB_CHECK3D(ZDZ,"GRIDPROJ:ZDZ",PRECISION) CALL MPPDB_CHECK3D(ZDZ,"GRIDPROJ:ZDZ",PRECISION)
! !
!----------------------------------------------------------------------------- !-----------------------------------------------------------------------------
......
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