Skip to content
Snippets Groups Projects
shuman_device.f90 39.7 KiB
Newer Older
  • Learn to ignore specific revisions
  • 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(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 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
    
    !            
    !-------------------------------------------------------------------------------
    
    !
    !*       1.    DEFINITION OF DYF
    !              ------------------
    !
    IIU = SIZE(PA,1)
    IJU = SIZE(PA,2)
    IKU = SIZE(PA,3)
    !
    
    !$acc_nv loop independent collapse(3)
    !TODO: remplacer le 1 par JPHEXT ?
    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) 
    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
    
    !$acc_nv loop independent collapse(2)
    DO CONCURRENT ( JI=1:IIU , JK=1:IKU )   
       PDYF(JI,IJU-JPHEXT+JJ,JK) = PDYF(JI,JPHEXT+JJ,JK) ! for reprod JPHEXT <> 1
    END DO
    
    !-------------------------------------------------------------------------------
    !
    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
    
    !     
    !-------------------------------------------------------------------------------
    
    !
    !*       1.    DEFINITION OF DYM
    !              ------------------
    !
    IIU=SIZE(PA,1)
    IJU=SIZE(PA,2)
    IKU=SIZE(PA,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(PA,PDYM)
    !CDIR NODEP
    !OCL NOVREC
    DO JIJK=JIJKOR , JIJKEND
    
       PDYM(JIJK,1,1) = PA(JIJK,1,1)  -  PA(JIJK-IIU,1,1) 
    
    DO JJ=1,JPHEXT
       PDYM(:,JJ,:) = PDYM(:,IJU-2*JPHEXT+JJ,:) ! for reprod JPHEXT <> 1
    END DO
    
    !-------------------------------------------------------------------------------
    !
    END SUBROUTINE DYM_DEVICE
    !
    !     ###############################
    
    !     ###############################
    !
    !!****  *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
    
    !         
    !-------------------------------------------------------------------------------
    
    !
    !*       1.    DEFINITION OF DZF
    !              ------------------
    !
    IIU = SIZE(PA,1)
    IJU = SIZE(PA,2)
    IKU = SIZE(PA,3)
    !
    
    #ifndef _OPT_LINEARIZED_LOOPS
    !$acc kernels present(PA,PDZF)
    
    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(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
    
    !-------------------------------------------------------------------------------
    !
    END SUBROUTINE DZF_DEVICE
    !
    !     ###############################
    
    !     ###############################
    !
    !!****  *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
    
    !           
    !-------------------------------------------------------------------------------
    
    !
    !*       1.    DEFINITION OF DZM
    !              ------------------
    !
    IIU = SIZE(PA,1)
    IJU = SIZE(PA,2)
    IKU = SIZE(PA,3)
    !
    
    #ifndef _OPT_LINEARIZED_LOOPS
    !$acc kernels present(PA,PDZM)
    
    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(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
    
    !-------------------------------------------------------------------------------
    !
    END SUBROUTINE DZM_DEVICE