!MNH_LIC Copyright 1994-2022 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. !----------------------------------------------------------------- #ifdef MNH_OPENACC ! ######################### MODULE MODI_SHUMAN_DEVICE ! ######################### ! INTERFACE ! SUBROUTINE DXF_DEVICE(PA,PDXF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDXF ! result at mass localization END SUBROUTINE DXF_DEVICE ! SUBROUTINE DXM_DEVICE(PA,PDXM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDXM ! result at flux side END SUBROUTINE DXM_DEVICE ! SUBROUTINE DYF_DEVICE(PA,PDYF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDYF ! result at mass localization END SUBROUTINE DYF_DEVICE ! SUBROUTINE DYM_DEVICE(PA,PDYM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDYM ! result at flux side END SUBROUTINE DYM_DEVICE ! SUBROUTINE DZF_DEVICE(PA,PDZF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDZF ! result at mass localization END SUBROUTINE DZF_DEVICE ! SUBROUTINE DZM_DEVICE(PA,PDZM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDZM ! result at flux side END SUBROUTINE DZM_DEVICE ! SUBROUTINE MXF_DEVICE(PA,PMXF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMXF ! result at mass localization END SUBROUTINE MXF_DEVICE ! SUBROUTINE MXM_DEVICE(PA,PMXM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMXM ! result at flux localization END SUBROUTINE MXM_DEVICE ! SUBROUTINE MYF_DEVICE(PA,PMYF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMYF ! result at mass localization END SUBROUTINE MYF_DEVICE ! SUBROUTINE MYM_DEVICE(PA,PMYM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMYM ! result at flux localization END SUBROUTINE MYM_DEVICE ! SUBROUTINE MZF_DEVICE(PA,PMZF) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMZF ! result at mass localization END SUBROUTINE MZF_DEVICE ! SUBROUTINE MZM_DEVICE(PA,PMZM) REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMZM ! result at flux localization END SUBROUTINE MZM_DEVICE ! END INTERFACE ! END MODULE MODI_SHUMAN_DEVICE ! ! ! ############################### SUBROUTINE MXF_DEVICE(PA,PMXF) ! ############################### ! !!**** *MXF* - Shuman operator : mean operator in x direction for a !! variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the x direction (I index) for a field PA localized at a x-flux ! point (u point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PMXF(i,:,:) is defined by 0.5*(PA(i,:,:)+PA(i+1,:,:)) !! At i=size(PA,1), PMXF(i,:,:) are replaced by the values of PMXF, !! which are the right values in the x-cyclic case !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMXF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JJK INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMXF ) ! !* 1. DEFINITION OF MXF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PMXF,PA) !$acc loop independent collapse(3) DO JK = 1, IKU DO JJ = 1, IJU DO JI = 1 + 1, IIU PMXF(JI-1,JJ,JK) = 0.5*( PA(JI-1,JJ,JK)+PA(JI,JJ,JK) ) ENDDO ENDDO ENDDO ! PMXF(IIU,:,:) = PMXF(2*JPHEXT,:,:) !$acc end kernels #else JIJKOR = 1 + 1 JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PMXF,PA) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PMXF(JIJK-1,1,1) = 0.5*( PA(JIJK-1,1,1)+PA(JIJK,1,1) ) END DO ! !CDIR NODEP !OCL NOVREC DO JI=1,JPHEXT DO JJK=1,IJU*IKU PMXF(IIU-JPHEXT+JI,JJK,1) = PMXF(JPHEXT+JI,JJK,1) ! for reprod JPHEXT <> 1 END DO END DO !$acc end kernels #endif !$acc end data ! !------------------------------------------------------------------------------- ! END SUBROUTINE MXF_DEVICE ! ! ############################### SUBROUTINE MXM_DEVICE(PA,PMXM) ! ############################### ! !!**** *MXM* - Shuman operator : mean operator in x direction for a !! mass variable !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the x direction (I index) for a field PA localized at a mass ! point. The result is localized at a x-flux point (u point). ! !!** METHOD !! ------ !! The result PMXM(i,:,:) is defined by 0.5*(PA(i,:,:)+PA(i-1,:,:)) !! At i=1, PMXM(1,:,:) are replaced by the values of PMXM, !! which are the right values in the x-cyclic case. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMXM ! result at flux localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JJK INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMXM ) ! !* 1. DEFINITION OF MXM ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PMXM) !$acc loop independent collapse(3) DO JK = 1, IKU DO JJ = 1, IJU DO JI = 1 + 1, IIU PMXM(JI,JJ,JK) = 0.5*( PA(JI,JJ,JK)+PA(JI-1,JJ,JK) ) ENDDO ENDDO ENDDO ! !$acc loop independent collapse(2) DO JK = 1, IKU DO JJ=1,IJU PMXM(1,JJ,JK) = PMXM(IIU-2*JPHEXT+1,JJ,JK) !TODO: voir si ce n'est pas plutot JPHEXT+1 ENDDO ENDDO !$acc end kernels #else JIJKOR = 1 + 1 JIJKEND = IIU*IJU*IKU ! !CDIR NODEP !OCL NOVREC !$acc kernels present_crm(PA,PMXM) DO JIJK=JIJKOR , JIJKEND PMXM(JIJK,1,1) = 0.5*( PA(JIJK,1,1)+PA(JIJK-1,1,1) ) END DO ! !CDIR NODEP !OCL NOVREC DO JI=1,JPHEXT DO JJK=1,IJU*IKU PMXM(JI,JJK,1) = PMXM(IIU-2*JPHEXT+JI,JJK,1) ! for reprod JPHEXT <> 1 END DO END DO !$acc end kernels #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE MXM_DEVICE ! ! ############################### SUBROUTINE MYF_DEVICE(PA,PMYF) ! ############################### ! !!**** *MYF* - Shuman operator : mean operator in y direction for a !! variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the y direction (J index) for a field PA localized at a y-flux ! point (v point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PMYF(i,:,:) is defined by 0.5*(PA(:,j,:)+PA(:,j+1,:)) !! At j=size(PA,2), PMYF(:,j,:) are replaced by the values of PMYF, !! which are the right values in the y-cyclic case !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMYF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMYF ) ! !* 1. DEFINITION OF MYF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! !$acc kernels present_crm(PA,PMYF) #ifndef _OPT_LINEARIZED_LOOPS !TODO: remplacer le 1 par JPHEXT ? !$mnh_do_concurrent(JI=1:IIU,JJ=1:IJU-1,JK=1:IKU) PMYF(JI,JJ,JK) = 0.5*( PA(JI,JJ,JK)+PA(JI,JJ+1,JK) ) !$mnh_end_do() #else JIJKOR = 1 + IIU JIJKEND = IIU*IJU*IKU ! !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PMYF(JIJK-IIU,1,1) = 0.5*( PA(JIJK-IIU,1,1)+PA(JIJK,1,1) ) END DO #endif ! !$mnh_do_concurrent(JI=1:IIU,JJ=1:JPHEXT,JK=1:IKU) PMYF(JI,IJU-JPHEXT+JJ,JK) = PMYF(JI,JPHEXT+JJ,JK) ! for reprod JPHEXT <> 1 !$mnh_end_do() !$acc end kernels !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE MYF_DEVICE ! ! ############################### SUBROUTINE MYM_DEVICE(PA,PMYM) ! ############################### ! !!**** *MYM* - Shuman operator : mean operator in y direction for a !! mass variable !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the y direction (J index) for a field PA localized at a mass ! point. The result is localized at a y-flux point (v point). ! !!** METHOD !! ------ !! The result PMYM(:,j,:) is defined by 0.5*(PA(:,j,:)+PA(:,j-1,:)) !! At j=1, PMYM(:,j,:) are replaced by the values of PMYM, !! which are the right values in the y-cyclic case. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMYM ! result at flux localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JJK INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMYM ) ! !* 1. DEFINITION OF MYM ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PMYM) !TODO: remplacer le 1+1 par 1+JPHEXT ? !$mnh_do_concurrent(JI=1:IIU,JJ=2:IJU,JK=1:IKU) PMYM(JI,JJ,JK) = 0.5*( PA(JI,JJ,JK)+PA(JI,JJ-1,JK) ) !$mnh_end_do() #else JIJKOR = 1 + IIU JIJKEND = IIU*IJU*IKU !CDIR NODEP !OCL NOVREC !$acc kernels present_crm(PA,PMYM) DO JIJK=JIJKOR , JIJKEND PMYM(JIJK,1,1) = 0.5*( PA(JIJK,1,1)+PA(JIJK-IIU,1,1) ) END DO #endif ! !$mnh_do_concurrent(JI=1:IIU,JJ=1:JPHEXT,JK=1:IKU) PMYM(JI,JJ,JK) = PMYM(JI,IJU-2*JPHEXT+JJ,JK) ! for reprod JPHEXT <> 1 !$mnh_end_do() !$acc end kernels !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE MYM_DEVICE ! ! ############################### SUBROUTINE MZF_DEVICE(PA,PMZF) ! ############################### ! !!**** *MZF* - Shuman operator : mean operator in z direction for a !! variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the z direction (K index) for a field PA localized at a z-flux ! point (w point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PMZF(:,:,k) is defined by 0.5*(PA(:,:,k)+PA(:,:,k+1)) !! At k=size(PA,3), PMZF(:,:,k) is defined by -999. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! NONE !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! optimisation 20/08/00 J. Escobar !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMZF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJ INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMZF ) ! !* 1. DEFINITION OF MZF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PMZF) PMZF(:,:,1:IKU-1) = 0.5*( PA(:,:,1:IKU-1)+PA(:,:,2:) ) ! PMZF(:,:,IKU) = -999. !$acc end kernels #else JIJKOR = 1 + IIU*IJU JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PMZF) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PMZF(JIJK-IIU*IJU,1,1) = 0.5*( PA(JIJK-IIU*IJU,1,1)+PA(JIJK,1,1) ) END DO ! !CDIR NODEP !OCL NOVREC DO JIJ=1,IIU*IJU PMZF(JIJ,1,IKU) = PMZF(JIJ,1,IKU-1) !-999. END DO !$acc end kernels #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE MZF_DEVICE ! ! ############################### SUBROUTINE MZM_DEVICE(PA,PMZM) ! ############################### ! !!**** *MZM* - Shuman operator : mean operator in z direction for a !! mass variable !! !! PURPOSE !! ------- ! The purpose of this function is to compute a mean ! along the z direction (K index) for a field PA localized at a mass ! point. The result is localized at a z-flux point (w point). ! !!** METHOD !! ------ !! The result PMZM(:,:,k) is defined by 0.5*(PA(:,:,k)+PA(:,:,k-1)) !! At k=1, PMZM(:,:,1) is defined by -999. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! NONE !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 04/07/94 !! optimisation 20/08/00 J. Escobar !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PMZM ! result at flux localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJ INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PMZM ) ! !* 1. DEFINITION OF MZM ! ------------------ ! #ifndef _OPT_LINEARIZED_LOOPS IKU = SIZE(PA,3) ! !$acc kernels present_crm(PA,PMZM) DO JK=2,IKU !TODO: remplacer le 2 par JPHEXT+1 ? PMZM(:,:,JK) = 0.5* ( PA(:,:,JK) + PA(:,:,JK-1) ) END DO ! PMZM(:,:,1) = -999. !$acc end kernels #else IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! JIJKOR = 1 + IIU*IJU JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PMZM) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PMZM(JIJK,1,1) = 0.5*( PA(JIJK,1,1)+PA(JIJK-IIU*IJU,1,1) ) END DO ! !CDIR NODEP !OCL NOVREC DO JIJ=1,IIU*IJU PMZM(JIJ,1,1) = -999. END DO !$acc end kernels ! #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE MZM_DEVICE ! ! ############################### SUBROUTINE DXF_DEVICE(PA,PDXF) ! ############################### ! !!**** *DXF* - Shuman operator : finite difference operator in x direction !! for a variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the x direction (I index) for a field PA localized at a x-flux ! point (u point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PDXF(i,:,:) is defined by (PA(i+1,:,:)-PA(i,:,:)) !! At i=size(PA,1), PDXF(i,:,:) are replaced by the values of PDXF, !! which are the right values in the x-cyclic case !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDXF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JJK INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDXF ) ! !* 1. DEFINITION OF DXF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PDXF) !$acc loop independent collapse(3) DO JK=1,IKU DO JJ=1,IJU DO JI=1+1,IIU PDXF(JI-1,JJ,JK) = PA(JI,JJ,JK) - PA(JI-1,JJ,JK) END DO END DO END DO ! !$acc loop independent collapse(2) DO JK=1,IKU DO JJ=1,IJU PDXF(IIU,JJ,JK) = PDXF(2*JPHEXT,JJ,JK) ENDDO ENDDO !$acc end kernels #else JIJKOR = 1 + 1 JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PDXF) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDXF(JIJK-1,1,1) = PA(JIJK,1,1) - PA(JIJK-1,1,1) END DO ! !CDIR NODEP !OCL NOVREC DO JI=1,JPHEXT DO JJK=1,IJU*IKU PDXF(IIU-JPHEXT+JI,JJK,1) = PDXF(JPHEXT+JI,JJK,1) ! for reprod JPHEXT <> 1 END DO END DO !$acc end kernels #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DXF_DEVICE ! ! ############################### SUBROUTINE DXM_DEVICE(PA,PDXM) ! ############################### ! !!**** *DXM* - Shuman operator : finite difference operator in x direction !! for a variable at a mass localization !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the x direction (I index) for a field PA localized at a mass ! point. The result is localized at a x-flux point (u point). ! !!** METHOD !! ------ !! The result PDXM(i,:,:) is defined by (PA(i,:,:)-PA(i-1,:,:)) !! At i=1, PDXM(1,:,:) are replaced by the values of PDXM, !! which are the right values in the x-cyclic case. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDXM ! result at flux side ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JJK INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDXM ) ! !* 1. DEFINITION OF DXM ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PDXM) !$acc loop independent collapse(3) DO JK=1,IKU DO JJ=1,IJU DO JI=1+1,IIU !TODO: remplacer le 1 par JPHEXT ? PDXM(JI,JJ,JK) = PA(JI,JJ,JK) - PA(JI-1,JJ,JK) END DO END DO END DO ! !$acc loop independent collapse(2) DO JK=1,IKU DO JJ=1,IJU PDXM(1,JJ,JK) = PDXM(IIU-2*JPHEXT+1,JJ,JK) !TODO: remplacer -2*JPHEXT+1 par -JPHEXT ? ENDDO ENDDO !$acc end kernels #else JIJKOR = 1 + 1 JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PDXM) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDXM(JIJK,1,1) = PA(JIJK,1,1) - PA(JIJK-1,1,1) END DO ! !CDIR NODEP !OCL NOVREC DO JI=1,JPHEXT DO JJK=1,IJU*IKU PDXM(JI,JJK,1) = PDXM(IIU-2*JPHEXT+JI,JJK,1) ! for reprod JPHEXT <> 1 END DO END DO !$acc end kernels #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DXM_DEVICE ! ! ############################### SUBROUTINE DYF_DEVICE(PA,PDYF) ! ############################### ! !!**** *DYF* - Shuman operator : finite difference operator in y direction !! for a variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the y direction (J index) for a field PA localized at a y-flux ! point (v point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PDYF(:,j,:) is defined by (PA(:,j+1,:)-PA(:,j,:)) !! At j=size(PA,2), PDYF(:,j,:) are replaced by the values of PDYM, !! which are the right values in the y-cyclic case !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDYF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDYF ) ! !* 1. DEFINITION OF DYF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! !$acc kernels present_crm(PA,PDYF) #ifndef _OPT_LINEARIZED_LOOPS !TODO: remplacer le 1 par JPHEXT ? !$mnh_do_concurrent(JI=1:IIU,JJ=1:IJU-1,JK=1:IKU) PDYF(JI,JJ,JK) = PA(JI,JJ+1,JK) - PA(JI,JJ,JK) !$mnh_end_do() #else JIJKOR = 1 + IIU JIJKEND = IIU*IJU*IKU ! !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDYF(JIJK-IIU,1,1) = PA(JIJK,1,1) - PA(JIJK-IIU,1,1) END DO #endif ! !$acc loop seq DO JJ=1,JPHEXT !$mnh_do_concurrent(JI=1:IIU,JK=1:IKU) PDYF(JI,IJU-JPHEXT+JJ,JK) = PDYF(JI,JPHEXT+JJ,JK) ! for reprod JPHEXT <> 1 !$mnh_end_do() END DO !$acc end kernels !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DYF_DEVICE ! ! ############################### SUBROUTINE DYM_DEVICE(PA,PDYM) ! ############################### ! !!**** *DYM* - Shuman operator : finite difference operator in y direction !! for a variable at a mass localization !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the y direction (J index) for a field PA localized at a mass ! point. The result is localized at a y-flux point (v point). ! !!** METHOD !! ------ !! The result PDYM(:,j,:) is defined by (PA(:,j,:)-PA(:,j-1,:)) !! At j=1, PDYM(:,1,:) are replaced by the values of PDYM, !! which are the right values in the y-cyclic case. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! Module MODD_PARAMETERS: declaration of parameter variables !! JPHEXT: define the number of marginal points out of the !! physical domain along the horizontal directions. !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! Modification to include the periodic case 13/10/94 J.Stein !! optimisation 20/08/00 J. Escobar !! correction of in halo/pseudo-cyclic calculation for JPHEXT<> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! USE MODD_PARAMETERS ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDYM ! result at flux side ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDYM ) ! !* 1. DEFINITION OF DYM ! ------------------ ! IIU=SIZE(PA,1) IJU=SIZE(PA,2) IKU=SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PDYM) !$acc loop independent collapse(3) DO JK=1,IKU DO JJ=2,IJU !TODO: remplacer le 2 par JPHEXT+1 ? DO JI=1,IIU PDYM(JI,JJ,JK) = PA(JI,JJ,JK) - PA(JI,JJ-1,JK) END DO END DO END DO ! #else JIJKOR = 1 + IIU JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PDYM) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDYM(JIJK,1,1) = PA(JIJK,1,1) - PA(JIJK-IIU,1,1) END DO #endif ! DO JJ=1,JPHEXT PDYM(:,JJ,:) = PDYM(:,IJU-2*JPHEXT+JJ,:) ! for reprod JPHEXT <> 1 END DO !$acc end kernels !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DYM_DEVICE ! ! ############################### SUBROUTINE DZF_DEVICE(PA,PDZF) ! ############################### ! !!**** *DZF* - Shuman operator : finite difference operator in z direction !! for a variable at a flux side !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the z direction (K index) for a field PA localized at a z-flux ! point (w point). The result is localized at a mass point. ! !!** METHOD !! ------ !! The result PDZF(:,:,k) is defined by (PA(:,:,k+1)-PA(:,:,k)) !! At k=size(PA,3), PDZF(:,:,k) is defined by -999. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! NONE !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! optimisation 20/08/00 J. Escobar !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at flux side REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDZF ! result at mass localization ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJ INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDZF ) ! !* 1. DEFINITION OF DZF ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PDZF) !$acc loop independent collapse(3) DO JK=1,IKU-1 !TODO: remplacer le 1 par JPHEXT ? DO JJ=1,IJU DO JI=1,IIU PDZF(JI,JJ,JK) = PA(JI,JJ,JK+1)-PA(JI,JJ,JK) END DO END DO END DO ! PDZF(:,:,IKU) = -999. !$acc end kernels #else JIJKOR = 1 + IIU*IJU JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PDZF) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDZF(JIJK-IIU*IJU,1,1) = PA(JIJK,1,1)-PA(JIJK-IIU*IJU,1,1) END DO ! !CDIR NODEP !OCL NOVREC DO JIJ=1,IIU*IJU PDZF(JIJ,1,IKU) = -999. END DO !$acc end kernels #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DZF_DEVICE ! ! ############################### SUBROUTINE DZM_DEVICE(PA,PDZM) ! ############################### ! !!**** *DZM* - Shuman operator : finite difference operator in z direction !! for a variable at a mass localization !! !! PURPOSE !! ------- ! The purpose of this function is to compute a finite difference ! along the z direction (K index) for a field PA localized at a mass ! point. The result is localized at a z-flux point (w point). ! !!** METHOD !! ------ !! The result PDZM(:,j,:) is defined by (PA(:,:,k)-PA(:,:,k-1)) !! At k=1, PDZM(:,:,k) is defined by -999. !! !! !! EXTERNAL !! -------- !! NONE !! !! IMPLICIT ARGUMENTS !! ------------------ !! NONE !! !! REFERENCE !! --------- !! Book2 of documentation of Meso-NH (SHUMAN operators) !! Technical specifications Report of The Meso-NH (chapters 3) !! !! !! AUTHOR !! ------ !! V. Ducrocq * Meteo France * !! !! MODIFICATIONS !! ------------- !! Original 05/07/94 !! optimisation 20/08/00 J. Escobar !------------------------------------------------------------------------------- ! !* 0. DECLARATIONS ! ------------ ! IMPLICIT NONE ! !* 0.1 Declarations of argument and result ! ------------------------------------ ! REAL, DIMENSION(:,:,:), INTENT(IN) :: PA ! variable at mass localization REAL, DIMENSION(:,:,:), INTENT(OUT) :: PDZM ! result at flux side ! !* 0.2 Declarations of local variables ! ------------------------------- ! INTEGER :: JI, JJ, JK ! Loop indices INTEGER :: IIU, IJU, IKU ! upper bounds of PA ! #ifdef _OPT_LINEARIZED_LOOPS INTEGER :: JIJ INTEGER :: JIJK,JIJKOR,JIJKEND #endif ! !------------------------------------------------------------------------------- !$acc data present_crm( PA, PDZM ) ! !* 1. DEFINITION OF DZM ! ------------------ ! IIU = SIZE(PA,1) IJU = SIZE(PA,2) IKU = SIZE(PA,3) ! #ifndef _OPT_LINEARIZED_LOOPS !$acc kernels present_crm(PA,PDZM) !$acc loop independent collapse(3) DO JK=2,IKU !TODO: remplacer le 1+1 par 1+JPHEXT ? DO JJ=1,IJU DO JI=1,IIU PDZM(JI,JJ,JK) = PA(JI,JJ,JK) - PA(JI,JJ,JK-1) END DO END DO END DO ! PDZM(:,:,1) = -999. !$acc end kernels #else JIJKOR = 1 + IIU*IJU JIJKEND = IIU*IJU*IKU ! !$acc kernels present_crm(PA,PDZM) !CDIR NODEP !OCL NOVREC DO JIJK=JIJKOR , JIJKEND PDZM(JIJK,1,1) = PA(JIJK,1,1)-PA(JIJK-IIU*IJU,1,1) END DO ! !CDIR NODEP !OCL NOVREC DO JIJ=1,IIU*IJU PDZM(JIJ,1,1) = -999. END DO #endif !$acc end data !------------------------------------------------------------------------------- ! END SUBROUTINE DZM_DEVICE #endif