diff --git a/src/MNH/advec_weno_k_2_aux.f90 b/src/MNH/advec_weno_k_2_aux.f90
index e5e1ad84a543f0983e457c773e6356dd989ad597..bff1ae2d720d538e877154a2cd16dd0068ed5609 100644
--- a/src/MNH/advec_weno_k_2_aux.f90
+++ b/src/MNH/advec_weno_k_2_aux.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-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.
@@ -351,7 +351,11 @@ IF (PRESENT(TPHALO2)) THEN
   TEAST => TPHALO2%EAST
 END IF
 #endif
-!
+
+#ifdef MNH_OPENACC
+  IF ( HLBCX(1) == 'CYCL' ) call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_UX', 'OpenACC: CYCL not yet tested' )
+#endif
+
 !$acc kernels
 PR(:,:,:) = 0.0
 !
@@ -375,10 +379,6 @@ SELECT CASE ( HLBCX(1) ) ! X direction LBC type: (1) for left side
 !*       1.1    CYCLIC CASE IN THE X DIRECTION:
 !
 CASE ('CYCL')          ! In that case one must have HLBCX(1) == HLBCX(2)
-#ifdef MNH_OPENACC
-  call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_UX', 'OpenACC: CYCL not yet tested' )
-#endif
-!
   IW=IIB
   IE=IIE
 !
@@ -734,7 +734,11 @@ IF (PRESENT(TPHALO2)) THEN
   TEAST => TPHALO2%EAST
 END IF
 #endif
-!
+
+#ifdef MNH_OPENACC
+  IF ( HLBCX(1) == 'CYCL' ) call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_MX', 'OpenACC: CYCL not yet tested' )
+#endif
+
 !$acc kernels
 PR(:,:,:) = 0.0
 !
@@ -758,10 +762,6 @@ SELECT CASE ( HLBCX(1) ) ! X direction LBC type: (1) for left side
 !*       1.1    CYCLIC CASE IN THE X DIRECTION:
 !
 CASE ('CYCL')          ! In that case one must have HLBCX(1) == HLBCX(2)
-#ifdef MNH_OPENACC
-  call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_MX', 'OpenACC: CYCL not yet tested' )
-#endif
-!
   IW=IIB
   IE=IIE
 !
@@ -1119,7 +1119,11 @@ IF (PRESENT(TPHALO2)) THEN
   TSOUTH => TPHALO2%SOUTH
 END IF
 #endif
-!
+
+#ifdef MNH_OPENACC
+  IF ( HLBCY(1) == 'CYCL' ) call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_MY', 'OpenACC: CYCL not yet tested' )
+#endif
+
 !$acc kernels
 PR(:,:,:) = 0.0
 !
@@ -1143,10 +1147,6 @@ SELECT CASE ( HLBCY(1) ) !
 !*       1.1    CYCLIC CASE IN THE Y DIRECTION:
 !
 CASE ('CYCL')          ! In that case one must have HLBCY(1) == HLBCY(2)
-#ifdef MNH_OPENACC
-  call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_MY', 'OpenACC: CYCL not yet tested' )
-#endif
-!
   IS=IJB
   IN=IJE
 !
@@ -1498,7 +1498,11 @@ IF (PRESENT(TPHALO2)) THEN
   TSOUTH => TPHALO2%SOUTH
 END IF
 #endif
-!
+
+#ifdef MNH_OPENACC
+  IF ( HLBCY(1) == 'CYCL' ) call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_VY', 'OpenACC: CYCL not yet tested' )
+#endif
+
 !$acc kernels
 PR(:,:,:) = 0.0
 !
@@ -1522,10 +1526,6 @@ SELECT CASE ( HLBCY(1) ) ! Y direction LBC type: (1) for left side
 !*       1.1    CYCLIC CASE IN THE Y DIRECTION:
 !
 CASE ('CYCL')          ! In that case one must have HLBCX(1) == HLBCX(2)
-#ifdef MNH_OPENACC
-  call Print_msg( NVERB_WARNING, 'GEN', 'ADVEC_WENO_K_2_VY', 'OpenACC: CYCL not yet tested' )
-#endif
-!
   IS=IJB
   IN=IJE
 !
diff --git a/src/MNH/advec_weno_k_3_aux.f90 b/src/MNH/advec_weno_k_3_aux.f90
index d6f20a6594252ca9521b528062cf36fbce91860b..fc7d56ff51318e24425e39b2ddf02522807fcfea 100644
--- a/src/MNH/advec_weno_k_3_aux.f90
+++ b/src/MNH/advec_weno_k_3_aux.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2013-2019 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2013-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.
@@ -413,6 +413,7 @@ PR(IW+1:IE-2,:,:) = (ZOMP1(IW+1:IE-2,:,:)/(ZOMP1(IW+1:IE-2,:,:)+ZOMP2(IW+1:IE-2,
                      + ZOMN3(IW+1:IE-2,:,:)/(ZOMN1(IW+1:IE-2,:,:)+ZOMN2(IW+1:IE-2,:,:)+ZOMN3(IW+1:IE-2,:,:)) &
                     * ZFNEG3(IW+1:IE-2,:,:))  & 
                     * (0.5-SIGN(0.5,PRUCT(IW+1:IE-2,:,:)))
+!$acc end kernels
 !
 !-------------------------------------------------------------------------------
 !*       1.2.   West border
@@ -432,6 +433,7 @@ CASE ('CYCL')
 !
 IF( LEAST_ll() .AND. .FALSE. ) THEN! East boundary is physical (monoproc)
 !
+!$acc kernels
 ! First positive stencil, needs indices i-2, i-1, i 
 ZFPOS1(IW,:,:)  = 1./6. * (2.0*PSRC(IE,:,:)   - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:))! Flux IW
 ZFPOS1(IW-1,:,:) = 1./6. * (2.0*PSRC(IE-1,:,:) - 7.0*PSRC(IE,:,:)   + 11.0*PSRC(IW-1,:,:))! Flux IW-1
@@ -459,9 +461,11 @@ ZBNEG3(IW-1,:,:) = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:
    + 1./4   * (PSRC(IE,:,:) - 4.0*PSRC(IW-1,:,:) + 3.0*PSRC(IW,:,:))**2! Smoothness indicator IW-1
 ZOMN3(IW-1:IW,:,:) = 3./10. / (ZEPS + ZBNEG3(IW-1:IW,:,:))**2! Non-normalized weight IW,IW-1
 ! 
+!$acc end kernels
 ELSEIF(IW>3) THEN! East boundary is proc border, with minimum 3 HALO points on west side
 !
-! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+! First positive stencil, needs indices i-2, i-1, i
 ZFPOS1(IW,:,:)   = 1./6. * (2.0*PSRC(IW-2,:,:)   - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:))! Flux IW
 ZFPOS1(IW-1,:,:) = 1./6. * (2.0*PSRC(IW-3,:,:) - 7.0*PSRC(IW-2,:,:)   + 11.0*PSRC(IW-1,:,:))! Flux IW-1
 ZBPOS1(IW,:,:)   = 13./12. * (PSRC(IW-1,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 & 
@@ -487,11 +491,13 @@ ZFNEG3(IW,:,:)   = 1./6 * (-1.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:)   + 2.0*PSRC(I
  ZBNEG3(IW-1,:,:) = 13./12 * (PSRC(IW-2,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 &
         + 1./4   * (PSRC(IW-2,:,:) - 4.0*PSRC(IW-1,:,:) + 3.0*PSRC(IW,:,:))**2 ! Smoothness indicator IW-1
  ZOMN3(IW-1:IW,:,:) = 3./10. / (ZEPS + ZBNEG3(IW-1:IW,:,:))**2 ! Non-normalized weight IW,IW-1
+!$acc end kernels
 !
  ELSE ! East boundary is proc border, with NHALO < 3 on west side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_UX','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on west side')
  ENDIF
 !
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(IW,:,:)   = 1./6 * (2.0*PSRC(IW,:,:) + 5.0*PSRC(IW+1,:,:) - PSRC(IW+2,:,:)) ! Flux IW
  ZFPOS3(IW-1,:,:) = 1./6 * (2.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:) - PSRC(IW+1,:,:)) ! Flux IW-1
@@ -529,6 +535,7 @@ ZFNEG3(IW,:,:)   = 1./6 * (-1.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:)   + 2.0*PSRC(I
                        + ZOMN2(IW-1:IW,:,:)/(ZOMN1(IW-1:IW,:,:)+ZOMN2(IW-1:IW,:,:)+ZOMN3(IW-1:IW,:,:)) * ZFNEG2(IW-1:IW,:,:) &
                        + ZOMN3(IW-1:IW,:,:)/(ZOMN1(IW-1:IW,:,:)+ZOMN2(IW-1:IW,:,:)+ZOMN3(IW-1:IW,:,:)) * ZFNEG3(IW-1:IW,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IW-1:IW,:,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -536,6 +543,7 @@ ZFNEG3(IW,:,:)   = 1./6 * (-1.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:)   + 2.0*PSRC(I
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IW-1
     PR(IW-1,:,:) = PSRC(IW-1,:,:) * (0.5+SIGN(0.5,PRUCT(IW-1,:,:))) + &
                    PSRC(IW,:,:) * &
@@ -563,7 +571,8 @@ ZFNEG3(IW,:,:)   = 1./6 * (-1.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:)   + 2.0*PSRC(I
      (ZOMP2(IW,:,:)/(ZOMP1(IW,:,:)+ZOMP2(IW,:,:)) * ZFPOS2(IW,:,:) + &
      (ZOMP1(IW,:,:)/(ZOMP1(IW,:,:)+ZOMP2(IW,:,:)) * ZFPOS1(IW,:,:))) &
      *(0.5+SIGN(0.5,PRUCT(IW,:,:)))  ! Total flux
-! 
+!$acc end kernels
+!
  END SELECT ! SELECT CASE (HLBCX(1)) ! X direction LBC type on left side
 !
 ELSE
@@ -580,7 +589,8 @@ ELSE
 !
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(IW,:,:)   = 1./6. * (2.0*PSRC(IW-2,:,:) - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:)) ! Flux IW
  ZFPOS1(IW-1,:,:) = 1./6. * (2.0*PSRC(IW-3,:,:) - 7.0*PSRC(IW-2,:,:) + 11.0*PSRC(IW-1,:,:)) ! Flux IW-1
  ZBPOS1(IW,:,:)   = 13./12. * (PSRC(IW-2,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 & 
@@ -647,6 +657,7 @@ ELSE
                        + ZOMN3(IW-1:IW,:,:)/(ZOMN1(IW-1:IW,:,:)+ZOMN2(IW-1:IW,:,:)+ZOMN3(IW-1:IW,:,:)) * ZFNEG3(IW-1:IW,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IW-1:IW,:,:)))
 !
+!$acc end kernels
  END IF ! NHALO
 !
 END IF ! IF(LWEST_ll()) 
@@ -670,6 +681,7 @@ IF( LEAST_ll() ) THEN
 ! 
  IF (LWEST_ll() .AND. .FALSE. ) THEN  ! West boundary is physical (monoproc)
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(IE-1,:,:) = 1./6 * (2.0*PSRC(IE-1,:,:) + 5.0*PSRC(IE,:,:) - PSRC(IE+1,:,:)) ! Flux IE-1
  ZFPOS3(IE,:,:)   = 1./6 * (2.0*PSRC(IE,:,:) + 5.0*PSRC(IE+1,:,:) - PSRC(IW,:,:)) ! Flux IE
@@ -696,9 +708,11 @@ IF( LEAST_ll() ) THEN
  ZBNEG2(IE,:,:)   = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IE+1,:,:) + PSRC(IW,:,:))**2 &
       + 1./4   * (PSRC(IE,:,:) -                      PSRC(IW,:,:))**2  ! Smoothness indicator IE
  ZOMN2(IE-1:IE,:,:) = 3./5. / (ZEPS + ZBNEG2(IE-1:IE,:,:))**2 ! Non-normalized weight IE-1,IE
+!$acc end kernels
 !
  ELSEIF(IE<=SIZE(PSRC,1)-3) THEN ! West boundary is proc border, with minimum 3 HALO points on east side
 !
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(IE-1,:,:) = 1./6 * (2.0*PSRC(IE-1,:,:) + 5.0*PSRC(IE,:,:) - PSRC(IE+1,:,:)) ! Flux IE-1
  ZFPOS3(IE,:,:)   = 1./6 * (2.0*PSRC(IE,:,:) + 5.0*PSRC(IE+1,:,:) - PSRC(IE+2,:,:)) ! Flux IE
@@ -725,12 +739,14 @@ IF( LEAST_ll() ) THEN
  ZBNEG2(IE,:,:)   = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IE+1,:,:) + PSRC(IE+2,:,:))**2 &
       + 1./4   * (PSRC(IE,:,:) -                      PSRC(IE+2,:,:))**2  ! Smoothness indicator IE
  ZOMN2(IE-1:IE,:,:) = 3./5. / (ZEPS + ZBNEG2(IE-1:IE,:,:))**2 ! Non-normalized weight IE-1,IE
+!$acc end kernels
 !
  ELSE ! West boundary is proc border, with NHALO < 3 on east side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_UX','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on east side')
  ENDIF
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(IE-1,:,:) = 1./6. * (2.0*PSRC(IE-3,:,:) - 7.0*PSRC(IE-2,:,:) + 11.0*PSRC(IE-1,:,:)) ! Flux IE-1
  ZFPOS1(IE,:,:)   = 1./6. * (2.0*PSRC(IE-2,:,:) - 7.0*PSRC(IE-1,:,:) + 11.0*PSRC(IE,:,:)) ! Flux IE
  ZBPOS1(IE-1,:,:) = 13./12. * (PSRC(IE-3,:,:) - 2.0*PSRC(IE-2,:,:) +     PSRC(IE-1,:,:))**2 & 
@@ -767,6 +783,7 @@ IF( LEAST_ll() ) THEN
                        + ZOMN2(IE-1:IE,:,:)/(ZOMN1(IE-1:IE,:,:)+ZOMN2(IE-1:IE,:,:)+ZOMN3(IE-1:IE,:,:)) * ZFNEG2(IE-1:IE,:,:) &
                        + ZOMN3(IE-1:IE,:,:)/(ZOMN1(IE-1:IE,:,:)+ZOMN2(IE-1:IE,:,:)+ZOMN3(IE-1:IE,:,:)) * ZFNEG3(IE-1:IE,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IE-1:IE,:,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -774,6 +791,7 @@ IF( LEAST_ll() ) THEN
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IE
     PR(IE,:,:) = PSRC(IE,:,:) * (0.5+SIGN(0.5,PRUCT(IE,:,:))) + &
                  PSRC(IE+1,:,:) * &
@@ -801,7 +819,8 @@ IF( LEAST_ll() ) THEN
                  (ZOMP2(IE-1,:,:)/(ZOMP1(IE-1,:,:)+ZOMP2(IE-1,:,:))*ZFPOS2(IE-1,:,:) + &
                    (ZOMP1(IE-1,:,:)/(ZOMP1(IE-1,:,:)+ZOMP2(IE-1,:,:))*ZFPOS1(IE-1,:,:))) &
       * (0.5+SIGN(0.5,PRUCT(IE-1,:,:)))  ! Total flux
-! 
+!$acc end kernels
+!
  END SELECT ! SELECT CASE (HLBCX(2)) ! X direction LBC type on right side
 !
 ELSE
@@ -818,7 +837,8 @@ ELSE
 ! 
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(IE-1,:,:) = 1./6. * (2.0*PSRC(IE-3,:,:) - 7.0*PSRC(IE-2,:,:) + 11.0*PSRC(IE-1,:,:)) ! Flux IE-1
  ZFPOS1(IE,:,:)   = 1./6. * (2.0*PSRC(IE-2,:,:) - 7.0*PSRC(IE-1,:,:) + 11.0*PSRC(IE,:,:)) ! Flux IE
  ZBPOS1(IE-1,:,:) = 13./12. * (PSRC(IE-3,:,:) - 2.0*PSRC(IE-2,:,:) +     PSRC(IE-1,:,:))**2 & 
@@ -885,11 +905,13 @@ ELSE
                        + ZOMN3(IE-1:IE,:,:)/(ZOMN1(IE-1:IE,:,:)+ZOMN2(IE-1:IE,:,:)+ZOMN3(IE-1:IE,:,:)) * ZFNEG3(IE-1:IE,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IE-1:IE,:,:)))
 ! 
+!$acc end kernels
  END IF ! NHALO
 !
 END IF ! IF(LWEST_ll()) 
 !-------------------------------------------------------------------------------
 !
+!$acc kernels
 PR = PR * PRUCT ! Add contravariant flux
 !$acc end kernels
 !
@@ -1094,6 +1116,7 @@ PR(IW+2:IE-1,:,:) = (ZOMP1(IW+2:IE-1,:,:)/(ZOMP1(IW+2:IE-1,:,:)+ZOMP2(IW+2:IE-1,
                      + ZOMN3(IW+2:IE-1,:,:)/(ZOMN1(IW+2:IE-1,:,:)+ZOMN2(IW+2:IE-1,:,:)+ZOMN3(IW+2:IE-1,:,:)) &
            * ZFNEG3(IW+2:IE-1,:,:))  & 
                     * (0.5-SIGN(0.5,PRUCT(IW+2:IE-1,:,:)))
+!$acc end kernels
 !
 !-------------------------------------------------------------------------------
 !*       1.2.   West border
@@ -1113,7 +1136,8 @@ IF( LWEST_ll() ) THEN
 !
  IF(LEAST_ll()  .AND. .FALSE. ) THEN  ! East border is physical
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(IW+1,:,:) = 1./6. * (2.0*PSRC(IE,:,:)   - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:)) ! Flux IW+1
  ZFPOS1(IW,:,:)   = 1./6. * (2.0*PSRC(IE-1,:,:) - 7.0*PSRC(IE,:,:)   + 11.0*PSRC(IW-1,:,:)) ! Flux IW
  ZBPOS1(IW+1,:,:) = 13./12. * (PSRC(IE,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 & 
@@ -1139,10 +1163,12 @@ IF( LWEST_ll() ) THEN
  ZBNEG3(IW,:,:)   = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 &
         + 1./4   * (PSRC(IE,:,:) - 4.0*PSRC(IW-1,:,:) + 3.0*PSRC(IW,:,:))**2 ! Smoothness indicator IW
  ZOMN3(IW:IW+1,:,:) = 3./10. / (ZEPS + ZBNEG3(IW:IW+1,:,:))**2 ! Non-normalized weight IW+1,IW
+!$acc end kernels
 !
  ELSEIF(IW>3) THEN ! East boundary is proc border, with minimum 3 HALO points on west side
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(IW+1,:,:) = 1./6. * (2.0*PSRC(IW-2,:,:)   - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:)) ! Flux IW+1
  ZFPOS1(IW,:,:)   = 1./6. * (2.0*PSRC(IW-3,:,:) - 7.0*PSRC(IW-2,:,:)   + 11.0*PSRC(IW-1,:,:)) ! Flux IW
  ZBPOS1(IW+1,:,:) = 13./12. * (PSRC(IW-2,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 & 
@@ -1168,11 +1194,13 @@ IF( LWEST_ll() ) THEN
  ZBNEG3(IW,:,:)   = 13./12 * (PSRC(IW-2,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 &
         + 1./4   * (PSRC(IW-2,:,:) - 4.0*PSRC(IW-1,:,:) + 3.0*PSRC(IW,:,:))**2 ! Smoothness indicator IW
  ZOMN3(IW:IW+1,:,:) = 3./10. / (ZEPS + ZBNEG3(IW:IW+1,:,:))**2 ! Non-normalized weight IW+1,IW
+!$acc end kernels
 !
  ELSE ! East boundary is proc border, with NHALO < 3 on west side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_MX','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on west side')
  ENDIF
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i-1, i, i+1
  ZFPOS3(IW+1,:,:) = 1./6 * (2.0*PSRC(IW,:,:) + 5.0*PSRC(IW+1,:,:) - PSRC(IW+2,:,:)) ! Flux IW+1
  ZFPOS3(IW,:,:)   = 1./6 * (2.0*PSRC(IW-1,:,:) + 5.0*PSRC(IW,:,:) - PSRC(IW+1,:,:)) ! Flux IW
@@ -1212,12 +1240,14 @@ IF( LWEST_ll() ) THEN
                        + ZOMN2(IW:IW+1,:,:)/(ZOMN1(IW:IW+1,:,:)+ZOMN2(IW:IW+1,:,:)+ZOMN3(IW:IW+1,:,:)) * ZFNEG2(IW:IW+1,:,:) &
                        + ZOMN3(IW:IW+1,:,:)/(ZOMN1(IW:IW+1,:,:)+ZOMN2(IW:IW+1,:,:)+ZOMN3(IW:IW+1,:,:)) * ZFNEG3(IW:IW+1,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IW:IW+1,:,:)))
+!$acc end kernels
 !
  CASE ('OPEN','WALL','NEST') 
  !---------------------------------------------------------------------------
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IW
     PR(IW,:,:) = PSRC(IW-1,:,:) * (0.5+SIGN(0.5,PRUCT(IW,:,:))) + &
                  PSRC(IW,:,:)  * (0.5-SIGN(0.5,PRUCT(IW,:,:)))
@@ -1244,6 +1274,7 @@ IF( LWEST_ll() ) THEN
       (ZOMP2(IW+1,:,:)/(ZOMP1(IW+1,:,:)+ZOMP2(IW+1,:,:)) * ZFPOS2(IW+1,:,:) + &
       (ZOMP1(IW+1,:,:)/(ZOMP1(IW+1,:,:)+ZOMP2(IW+1,:,:)) * ZFPOS1(IW+1,:,:))) &
       *(0.5+SIGN(0.5,PRUCT(IW+1,:,:)))  ! Total flux
+!$acc end kernels
 !
  END SELECT ! SELECT CASE (HLBCX(1)) ! X direction LBC type on left side
 !
@@ -1261,7 +1292,8 @@ ELSE
 !
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(IW+1,:,:) = 1./6. * (2.0*PSRC(IW-2,:,:)   - 7.0*PSRC(IW-1,:,:) + 11.0*PSRC(IW,:,:)) ! Flux IW+1
  ZFPOS1(IW,:,:)   = 1./6. * (2.0*PSRC(IW-3,:,:) - 7.0*PSRC(IW-2,:,:)   + 11.0*PSRC(IW-1,:,:)) ! Flux IW
  ZBPOS1(IW+1,:,:) = 13./12. * (PSRC(IW-2,:,:) - 2.0*PSRC(IW-1,:,:) +     PSRC(IW,:,:))**2 & 
@@ -1327,6 +1359,7 @@ ELSE
                        + ZOMN2(IW:IW+1,:,:)/(ZOMN1(IW:IW+1,:,:)+ZOMN2(IW:IW+1,:,:)+ZOMN3(IW:IW+1,:,:)) * ZFNEG2(IW:IW+1,:,:) &
                        + ZOMN3(IW:IW+1,:,:)/(ZOMN1(IW:IW+1,:,:)+ZOMN2(IW:IW+1,:,:)+ZOMN3(IW:IW+1,:,:)) * ZFNEG3(IW:IW+1,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IW:IW+1,:,:)))
+!$acc end kernels
 !
  END IF ! NHALO
 !
@@ -1350,6 +1383,7 @@ IF(LEAST_ll() ) THEN
 !
  IF(LWEST_ll()  .AND. .FALSE. ) THEN  ! West border is physical 
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(IE,:,:)   = 1./6 * (2.0*PSRC(IE-1,:,:) + 5.0*PSRC(IE,:,:) - PSRC(IE+1,:,:)) ! Flux IE
  ZFPOS3(IE+1,:,:) = 1./6 * (2.0*PSRC(IE,:,:) + 5.0*PSRC(IE+1,:,:) - PSRC(IW,:,:)) ! Flux IE+1
@@ -1376,9 +1410,11 @@ IF(LEAST_ll() ) THEN
  ZBNEG2(IE+1,:,:) = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IE+1,:,:) + PSRC(IW,:,:))**2 &
       + 1./4   * (PSRC(IE,:,:) -                      PSRC(IW,:,:))**2  ! Smoothness indicator IE+1
  ZOMN2(IE:IE+1,:,:) = 3./5. / (ZEPS + ZBNEG2(IE:IE+1,:,:))**2 ! Non-normalized weight IE,IE+1
+!$acc end kernels
 !
  ELSEIF(IE<=SIZE(PSRC,1)-3) THEN ! West boundary is proc border, with minimum 3 HALO points on east side
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(IE,:,:)   = 1./6 * (2.0*PSRC(IE-1,:,:) + 5.0*PSRC(IE,:,:) - PSRC(IE+1,:,:)) ! Flux IE
  ZFPOS3(IE+1,:,:) = 1./6 * (2.0*PSRC(IE,:,:) + 5.0*PSRC(IE+1,:,:) - PSRC(IE+2,:,:)) ! Flux IE+1
@@ -1405,12 +1441,14 @@ IF(LEAST_ll() ) THEN
  ZBNEG2(IE+1,:,:) = 13./12 * (PSRC(IE,:,:) - 2.0*PSRC(IE+1,:,:) + PSRC(IE+2,:,:))**2 &
       + 1./4   * (PSRC(IE,:,:) -                      PSRC(IE+2,:,:))**2  ! Smoothness indicator IE+1
  ZOMN2(IE:IE+1,:,:) = 3./5. / (ZEPS + ZBNEG2(IE:IE+1,:,:))**2 ! Non-normalized weight IE,IE+1
+!$acc end kernels
 !
  ELSE ! West boundary is proc border, with NHALO < 3 on east side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_MX','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on east side')
  ENDIF
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(IE,:,:)   = 1./6. * (2.0*PSRC(IE-3,:,:) - 7.0*PSRC(IE-2,:,:) + 11.0*PSRC(IE-1,:,:)) ! Flux IE
  ZFPOS1(IE+1,:,:) = 1./6. * (2.0*PSRC(IE-2,:,:) - 7.0*PSRC(IE-1,:,:) + 11.0*PSRC(IE,:,:)) ! Flux IE+1
  ZBPOS1(IE,:,:)   = 13./12. * (PSRC(IE-3,:,:) - 2.0*PSRC(IE-2,:,:) +     PSRC(IE-1,:,:))**2 & 
@@ -1447,6 +1485,7 @@ IF(LEAST_ll() ) THEN
                        + ZOMN2(IE:IE+1,:,:)/(ZOMN1(IE:IE+1,:,:)+ZOMN2(IE:IE+1,:,:)+ZOMN3(IE:IE+1,:,:)) * ZFNEG2(IE:IE+1,:,:) &
                        + ZOMN3(IE:IE+1,:,:)/(ZOMN1(IE:IE+1,:,:)+ZOMN2(IE:IE+1,:,:)+ZOMN3(IE:IE+1,:,:)) * ZFNEG3(IE:IE+1,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IE:IE+1,:,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -1454,6 +1493,7 @@ IF(LEAST_ll() ) THEN
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IE+1
     PR(IE+1,:,:) = PSRC(IE,:,:)  * (0.5+SIGN(0.5,PRUCT(IE+1,:,:))) + &
                    PSRC(IE+1,:,:) * (0.5-SIGN(0.5,PRUCT(IE+1,:,:)))
@@ -1481,6 +1521,7 @@ IF(LEAST_ll() ) THEN
                  (ZOMP1(IE,:,:)/(ZOMP1(IE,:,:)+ZOMP2(IE,:,:))*ZFPOS1(IE,:,:))) &
      *(0.5+SIGN(0.5,PRUCT(IE,:,:)))  ! Total flux
 ! 
+!$acc end kernels
  END SELECT ! SELECT CASE (HLBCX(2)) ! X direction LBC type on right side
 !
 ELSE
@@ -1497,7 +1538,8 @@ ELSE
 ! 
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(IE,:,:)   = 1./6. * (2.0*PSRC(IE-3,:,:) - 7.0*PSRC(IE-2,:,:) + 11.0*PSRC(IE-1,:,:)) ! Flux IE
  ZFPOS1(IE+1,:,:) = 1./6. * (2.0*PSRC(IE-2,:,:) - 7.0*PSRC(IE-1,:,:) + 11.0*PSRC(IE,:,:)) ! Flux IE+1
  ZBPOS1(IE,:,:)   = 13./12. * (PSRC(IE-3,:,:) - 2.0*PSRC(IE-2,:,:) +     PSRC(IE-1,:,:))**2 & 
@@ -1563,12 +1605,14 @@ ELSE
                        + ZOMN2(IE:IE+1,:,:)/(ZOMN1(IE:IE+1,:,:)+ZOMN2(IE:IE+1,:,:)+ZOMN3(IE:IE+1,:,:)) * ZFNEG2(IE:IE+1,:,:) &
                        + ZOMN3(IE:IE+1,:,:)/(ZOMN1(IE:IE+1,:,:)+ZOMN2(IE:IE+1,:,:)+ZOMN3(IE:IE+1,:,:)) * ZFNEG3(IE:IE+1,:,:)) &
                       * (0.5-SIGN(0.5,PRUCT(IE:IE+1,:,:)))
+!$acc end kernels
 !
  END IF ! NHALO
 !
 END IF ! IF(LWEST_ll()) 
 !-------------------------------------------------------------------------------
 !
+!$acc kernels
 PR = PR * PRUCT ! Add contravariant flux
 !$acc end kernels
 !
@@ -1776,6 +1820,7 @@ PR(:,IS+2:IN-1,:) = (ZOMP1(:,IS+2:IN-1,:)/(ZOMP1(:,IS+2:IN-1,:)+ZOMP2(:,IS+2:IN-
                      + ZOMN3(:,IS+2:IN-1,:)/(ZOMN1(:,IS+2:IN-1,:)+ZOMN2(:,IS+2:IN-1,:)+ZOMN3(:,IS+2:IN-1,:)) &
            * ZFNEG3(:,IS+2:IN-1,:))  & 
                     * (0.5-SIGN(0.5,PRVCT(:,IS+2:IN-1,:)))
+!$acc end kernels
 !
 !-------------------------------------------------------------------------------
 !*       1.2.   South border
@@ -1795,7 +1840,8 @@ IF(LSOUTH_ll()) THEN
 !
  IF(LNORTH_ll()  .AND. .FALSE. ) THEN ! North border is physical 
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(:,IS+1,:) = 1./6. * (2.0*PSRC(:,IN,:)   - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS+1
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IN-1,:) - 7.0*PSRC(:,IN,:)   + 11.0*PSRC(:,IS-1,:)) ! Flux IS
  ZBPOS1(:,IS+1,:) = 13./12. * (PSRC(:,IN,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -1821,10 +1867,12 @@ IF(LSOUTH_ll()) THEN
  ZBNEG3(:,IS,:)   = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 &
         + 1./4   * (PSRC(:,IN,:) - 4.0*PSRC(:,IS-1,:) + 3.0*PSRC(:,IS,:))**2 ! Smoothness indicator IS
  ZOMN3(:,IS:IS+1,:) = 3./10. / (ZEPS + ZBNEG3(:,IS:IS+1,:))**2 ! Non-normalized weight IS+1,IS
-! 
+!$acc end kernels
+!
  ELSEIF(IS>3) THEN ! North boundary is proc border, with minimum 3 HALO points on sounth side
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(:,IS+1,:) = 1./6. * (2.0*PSRC(:,IS-2,:)   - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS+1
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IS-3,:) - 7.0*PSRC(:,IS-2,:)   + 11.0*PSRC(:,IS-1,:)) ! Flux IS
  ZBPOS1(:,IS+1,:) = 13./12. * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -1850,11 +1898,13 @@ IF(LSOUTH_ll()) THEN
  ZBNEG3(:,IS,:)   = 13./12 * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 &
         + 1./4   * (PSRC(:,IS-2,:) - 4.0*PSRC(:,IS-1,:) + 3.0*PSRC(:,IS,:))**2 ! Smoothness indicator IS
  ZOMN3(:,IS:IS+1,:) = 3./10. / (ZEPS + ZBNEG3(:,IS:IS+1,:))**2 ! Non-normalized weight IS+1,IS
-! 
+!$acc end kernels
+!
  ELSE ! North boundary is proc border, with NHALO < 3 on south side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_MY','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on south side')
  ENDIF
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i-1, i, i+1
  ZFPOS3(:,IS+1,:) = 1./6 * (2.0*PSRC(:,IS,:) + 5.0*PSRC(:,IS+1,:) - PSRC(:,IS+2,:)) ! Flux IS+1
  ZFPOS3(:,IS,:)   = 1./6 * (2.0*PSRC(:,IS-1,:) + 5.0*PSRC(:,IS,:) - PSRC(:,IS+1,:)) ! Flux IS
@@ -1894,6 +1944,7 @@ IF(LSOUTH_ll()) THEN
                        + ZOMN2(:,IS:IS+1,:)/(ZOMN1(:,IS:IS+1,:)+ZOMN2(:,IS:IS+1,:)+ZOMN3(:,IS:IS+1,:)) * ZFNEG2(:,IS:IS+1,:) &
                        + ZOMN3(:,IS:IS+1,:)/(ZOMN1(:,IS:IS+1,:)+ZOMN2(:,IS:IS+1,:)+ZOMN3(:,IS:IS+1,:)) * ZFNEG3(:,IS:IS+1,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IS:IS+1,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -1901,6 +1952,7 @@ IF(LSOUTH_ll()) THEN
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IS
     PR(:,IS,:) = PSRC(:,IS-1,:) * (0.5+SIGN(0.5,PRVCT(:,IS,:))) + &
                  PSRC(:,IS,:)  * (0.5-SIGN(0.5,PRVCT(:,IS,:)))
@@ -1927,6 +1979,7 @@ IF(LSOUTH_ll()) THEN
       (ZOMN2(:,IS+1,:)/(ZOMN1(:,IS+1,:)+ZOMN2(:,IS+1,:)) * ZFNEG2(:,IS+1,:) + &
             (ZOMN1(:,IS+1,:)/(ZOMN1(:,IS+1,:)+ZOMN2(:,IS+1,:)) * ZFNEG1(:,IS+1,:))) &
           *(0.5-SIGN(0.5,PRVCT(:,IS+1,:)))  ! Total flux
+!$acc end kernels
 !
  END SELECT ! SELECT CASE (HLBCY(1)) ! Y direction LBC type on south side
 !
@@ -1944,7 +1997,8 @@ ELSE
 !
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(:,IS+1,:) = 1./6. * (2.0*PSRC(:,IS-2,:)   - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS+1
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IS-3,:) - 7.0*PSRC(:,IS-2,:)   + 11.0*PSRC(:,IS-1,:)) ! Flux IS
  ZBPOS1(:,IS+1,:) = 13./12. * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -2010,6 +2064,7 @@ ELSE
                        + ZOMN2(:,IS:IS+1,:)/(ZOMN1(:,IS:IS+1,:)+ZOMN2(:,IS:IS+1,:)+ZOMN3(:,IS:IS+1,:)) * ZFNEG2(:,IS:IS+1,:) &
                        + ZOMN3(:,IS:IS+1,:)/(ZOMN1(:,IS:IS+1,:)+ZOMN2(:,IS:IS+1,:)+ZOMN3(:,IS:IS+1,:)) * ZFNEG3(:,IS:IS+1,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IS:IS+1,:)))
+!$acc end kernels
 !
  END IF ! NHALO
 !
@@ -2033,6 +2088,7 @@ IF( LNORTH_ll() ) THEN
 !
  IF (LSOUTH_ll()  .AND. .FALSE. ) THEN ! South border is physical 
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(:,IN,:)   = 1./6 * (2.0*PSRC(:,IN-1,:) + 5.0*PSRC(:,IN,:) - PSRC(:,IN+1,:)) ! Flux IN
  ZFPOS3(:,IN+1,:) = 1./6 * (2.0*PSRC(:,IN,:) + 5.0*PSRC(:,IN+1,:) - PSRC(:,IS,:)) ! Flux IN+1
@@ -2059,9 +2115,11 @@ IF( LNORTH_ll() ) THEN
  ZBNEG2(:,IN+1,:) = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IN+1,:) + PSRC(:,IS,:))**2 &
       + 1./4   * (PSRC(:,IN,:) -                      PSRC(:,IS,:))**2  ! Smoothness indicator IN+1
  ZOMN2(:,IN:IN+1,:) = 3./5. / (ZEPS + ZBNEG2(:,IN:IN+1,:))**2 ! Non-normalized weight IN,IN+1
+!$acc end kernels
 !
  ELSEIF(IN<=SIZE(PSRC,2)-3) THEN ! South boundary is proc border, with minimum 3 HALO points on north side
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(:,IN,:)   = 1./6 * (2.0*PSRC(:,IN-1,:) + 5.0*PSRC(:,IN,:) - PSRC(:,IN+1,:)) ! Flux IN
  ZFPOS3(:,IN+1,:) = 1./6 * (2.0*PSRC(:,IN,:) + 5.0*PSRC(:,IN+1,:) - PSRC(:,IN+2,:)) ! Flux IN+1
@@ -2088,12 +2146,14 @@ IF( LNORTH_ll() ) THEN
  ZBNEG2(:,IN+1,:) = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IN+1,:) + PSRC(:,IN+2,:))**2 &
       + 1./4   * (PSRC(:,IN,:) -                      PSRC(:,IN+2,:))**2  ! Smoothness indicator IN+1
  ZOMN2(:,IN:IN+1,:) = 3./5. / (ZEPS + ZBNEG2(:,IN:IN+1,:))**2 ! Non-normalized weight IN,IN+1
+!$acc end kernels
 !
  ELSE ! South boundary is proc border, with NHALO < 3 on south side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_MY','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on south side')
  ENDIF
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(:,IN,:)   = 1./6. * (2.0*PSRC(:,IN-3,:) - 7.0*PSRC(:,IN-2,:) + 11.0*PSRC(:,IN-1,:)) ! Flux IN
  ZFPOS1(:,IN+1,:) = 1./6. * (2.0*PSRC(:,IN-2,:) - 7.0*PSRC(:,IN-1,:) + 11.0*PSRC(:,IN,:)) ! Flux IN+1
  ZBPOS1(:,IN,:)   = 13./12. * (PSRC(:,IN-3,:) - 2.0*PSRC(:,IN-2,:) +     PSRC(:,IN-1,:))**2 & 
@@ -2130,6 +2190,7 @@ IF( LNORTH_ll() ) THEN
                        + ZOMN2(:,IN:IN+1,:)/(ZOMN1(:,IN:IN+1,:)+ZOMN2(:,IN:IN+1,:)+ZOMN3(:,IN:IN+1,:)) * ZFNEG2(:,IN:IN+1,:) &
                        + ZOMN3(:,IN:IN+1,:)/(ZOMN1(:,IN:IN+1,:)+ZOMN2(:,IN:IN+1,:)+ZOMN3(:,IN:IN+1,:)) * ZFNEG3(:,IN:IN+1,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IN:IN+1,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -2137,6 +2198,7 @@ IF( LNORTH_ll() ) THEN
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IN+1
     PR(:,IN+1,:) = PSRC(:,IN,:)  * (0.5+SIGN(0.5,PRVCT(:,IN+1,:))) + &
                    PSRC(:,IN+1,:) * (0.5-SIGN(0.5,PRVCT(:,IN+1,:)))
@@ -2163,6 +2225,7 @@ IF( LNORTH_ll() ) THEN
      (ZOMN2(:,IN,:)/(ZOMN1(:,IN,:)+ZOMN2(:,IN,:))*ZFNEG2(:,IN,:) + &
      (ZOMN1(:,IN,:)/(ZOMN1(:,IN,:)+ZOMN2(:,IN,:))*ZFNEG1(:,IN,:))) &
      *(0.5-SIGN(0.5,PRVCT(:,IN,:)))  ! Total flux
+!$acc end kernels
 !
  END SELECT ! SELECT CASE (HLBCX(2)) ! X direction LBC type on right side
 !
@@ -2180,7 +2243,8 @@ ELSE
 ! 
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-3, i-2, i-1 
+!$acc kernels
+ ! First positive stencil, needs indices i-3, i-2, i-1
  ZFPOS1(:,IN,:)   = 1./6. * (2.0*PSRC(:,IN-3,:) - 7.0*PSRC(:,IN-2,:) + 11.0*PSRC(:,IN-1,:)) ! Flux IN
  ZFPOS1(:,IN+1,:) = 1./6. * (2.0*PSRC(:,IN-2,:) - 7.0*PSRC(:,IN-1,:) + 11.0*PSRC(:,IN,:)) ! Flux IN+1
  ZBPOS1(:,IN,:)   = 13./12. * (PSRC(:,IN-3,:) - 2.0*PSRC(:,IN-2,:) +     PSRC(:,IN-1,:))**2 & 
@@ -2246,12 +2310,14 @@ ELSE
                        + ZOMN2(:,IN:IN+1,:)/(ZOMN1(:,IN:IN+1,:)+ZOMN2(:,IN:IN+1,:)+ZOMN3(:,IN:IN+1,:)) * ZFNEG2(:,IN:IN+1,:) &
                        + ZOMN3(:,IN:IN+1,:)/(ZOMN1(:,IN:IN+1,:)+ZOMN2(:,IN:IN+1,:)+ZOMN3(:,IN:IN+1,:)) * ZFNEG3(:,IN:IN+1,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IN:IN+1,:)))
+!$acc end kernels
 !
  END IF ! NHALO
 !
 END IF ! IF(LNORTH_ll()) 
 !-------------------------------------------------------------------------------
 !
+!$acc kernels
 PR = PR * PRVCT ! Add contravariant flux
 !$acc end kernels
 !
@@ -2459,6 +2525,7 @@ PR(:,IS+1:IN-2,:) = (ZOMP1(:,IS+1:IN-2,:)/(ZOMP1(:,IS+1:IN-2,:)+ZOMP2(:,IS+1:IN-
                      + ZOMN3(:,IS+1:IN-2,:)/(ZOMN1(:,IS+1:IN-2,:)+ZOMN2(:,IS+1:IN-2,:)+ZOMN3(:,IS+1:IN-2,:)) &
            * ZFNEG3(:,IS+1:IN-2,:))  & 
                     * (0.5-SIGN(0.5,PRVCT(:,IS+1:IN-2,:)))
+!$acc end kernels
 !
 !-------------------------------------------------------------------------------
 !*       1.2.   South border
@@ -2478,7 +2545,8 @@ IF(LSOUTH_ll() ) THEN
 !
  IF(LNORTH_ll()  .AND. .FALSE. ) THEN ! North border is physical 
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IN,:)   - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS
  ZFPOS1(:,IS-1,:) = 1./6. * (2.0*PSRC(:,IN-1,:) - 7.0*PSRC(:,IN,:)   + 11.0*PSRC(:,IS-1,:)) ! Flux IS-1
  ZBPOS1(:,IS,:)   = 13./12. * (PSRC(:,IN,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -2504,10 +2572,12 @@ IF(LSOUTH_ll() ) THEN
  ZBNEG3(:,IS-1,:) = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 &
         + 1./4   * (PSRC(:,IN,:) - 4.0*PSRC(:,IS-1,:) + 3.0*PSRC(:,IS,:))**2 ! Smoothness indicator IS-1
  ZOMN3(:,IS-1:IS,:) = 3./10. / (ZEPS + ZBNEG3(:,IS-1:IS,:))**2 ! Non-normalized weight IS,IS-1
-! 
+!$acc end kernels
+!
  ELSEIF(IS>3) THEN ! North boundary is proc border, with minimum 3 HALO points on south side
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IS-2,:)   - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS
  ZFPOS1(:,IS-1,:) = 1./6. * (2.0*PSRC(:,IS+3,:) - 7.0*PSRC(:,IS-2,:)   + 11.0*PSRC(:,IS-1,:)) ! Flux IS-1
  ZBPOS1(:,IS,:)   = 13./12. * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -2533,11 +2603,13 @@ IF(LSOUTH_ll() ) THEN
  ZBNEG3(:,IS-1,:) = 13./12 * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 &
         + 1./4   * (PSRC(:,IS-2,:) - 4.0*PSRC(:,IS-1,:) + 3.0*PSRC(:,IS,:))**2 ! Smoothness indicator IS-1
  ZOMN3(:,IS-1:IS,:) = 3./10. / (ZEPS + ZBNEG3(:,IS-1:IS,:))**2 ! Non-normalized weight IS,IS-1
-! 
+!$acc end kernels
+!
  ELSE ! North boundary is proc border, with NHALO < 3 on south side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_VY','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on south side')
  ENDIF
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(:,IS,:)   = 1./6 * (2.0*PSRC(:,IS,:) + 5.0*PSRC(:,IS+1,:) - PSRC(:,IS+2,:)) ! Flux IS
  ZFPOS3(:,IS-1,:) = 1./6 * (2.0*PSRC(:,IS-1,:) + 5.0*PSRC(:,IS,:) - PSRC(:,IS+1,:)) ! Flux IS-1
@@ -2577,6 +2649,7 @@ IF(LSOUTH_ll() ) THEN
                        + ZOMN2(:,IS-1:IS,:)/(ZOMN1(:,IS-1:IS,:)+ZOMN2(:,IS-1:IS,:)+ZOMN3(:,IS-1:IS,:)) * ZFNEG2(:,IS-1:IS,:) &
                        + ZOMN3(:,IS-1:IS,:)/(ZOMN1(:,IS-1:IS,:)+ZOMN2(:,IS-1:IS,:)+ZOMN3(:,IS-1:IS,:)) * ZFNEG3(:,IS-1:IS,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IS-1:IS,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -2585,6 +2658,7 @@ IF(LSOUTH_ll() ) THEN
  !---------------------------------------------------------------------------
 !
  ! WENO scheme order 1, IS-1
+!$acc kernels
     PR(:,IS-1,:) = PSRC(:,IS-1,:) * (0.5+SIGN(0.5,PRVCT(:,IS-1,:))) + &
                    PSRC(:,IS,:) * &
                    (0.5-SIGN(0.5,PRVCT(:,IS-1,:)))
@@ -2611,7 +2685,8 @@ IF(LSOUTH_ll() ) THEN
      (ZOMP2(:,IS,:)/(ZOMP1(:,IS,:)+ZOMP2(:,IS,:)) * ZFPOS2(:,IS,:) + &
      (ZOMP1(:,IS,:)/(ZOMP1(:,IS,:)+ZOMP2(:,IS,:)) * ZFPOS1(:,IS,:))) &
      *(0.5+SIGN(0.5,PRVCT(:,IS,:)))  ! Total flux
-! 
+!$acc end kernels
+!
  END SELECT ! SELECT CASE (HLBCY(1)) ! Y direction LBC type on south side
 !
 ELSE
@@ -2628,7 +2703,8 @@ ELSE
 !
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(:,IS,:)   = 1./6. * (2.0*PSRC(:,IS-2,:) - 7.0*PSRC(:,IS-1,:) + 11.0*PSRC(:,IS,:)) ! Flux IS
  ZFPOS1(:,IS-1,:) = 1./6. * (2.0*PSRC(:,IS-3,:) - 7.0*PSRC(:,IS-2,:) + 11.0*PSRC(:,IS-1,:)) ! Flux IS-1
  ZBPOS1(:,IS,:)   = 13./12. * (PSRC(:,IS-2,:) - 2.0*PSRC(:,IS-1,:) +     PSRC(:,IS,:))**2 & 
@@ -2694,6 +2770,7 @@ ELSE
                        + ZOMN2(:,IS-1:IS,:)/(ZOMN1(:,IS-1:IS,:)+ZOMN2(:,IS-1:IS,:)+ZOMN3(:,IS-1:IS,:)) * ZFNEG2(:,IS-1:IS,:) &
                        + ZOMN3(:,IS-1:IS,:)/(ZOMN1(:,IS-1:IS,:)+ZOMN2(:,IS-1:IS,:)+ZOMN3(:,IS-1:IS,:)) * ZFNEG3(:,IS-1:IS,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IS-1:IS,:)))
+!$acc end kernels
 !
  END IF ! NHALO
 !
@@ -2717,6 +2794,7 @@ IF(LNORTH_ll()) THEN
 ! 
  IF(LSOUTH_ll()  .AND. .FALSE. ) THEN  ! South border is physical 
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(:,IN-1,:) = 1./6 * (2.0*PSRC(:,IN-1,:) + 5.0*PSRC(:,IN,:) - PSRC(:,IN+1,:)) ! Flux IN-1
  ZFPOS3(:,IN,:)   = 1./6 * (2.0*PSRC(:,IN,:) + 5.0*PSRC(:,IN+1,:) - PSRC(:,IS,:)) ! Flux IN
@@ -2743,9 +2821,11 @@ IF(LNORTH_ll()) THEN
  ZBNEG2(:,IN,:)   = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IN+1,:) + PSRC(:,IS,:))**2 &
       + 1./4   * (PSRC(:,IN,:) -                      PSRC(:,IS,:))**2  ! Smoothness indicator IN
  ZOMN2(:,IN-1:IN,:) = 3./5. / (ZEPS + ZBNEG2(:,IN-1:IN,:))**2 ! Non-normalized weight IN-1,IN
+!$acc end kernels
 !
  ELSEIF(IN<=SIZE(PSRC,2)-3) THEN ! South boundary is proc border, with minimum 3 HALO points on north side
 ! 
+!$acc kernels
  ! Third positive stencil, needs indices i, i+1, i+2
  ZFPOS3(:,IN-1,:) = 1./6 * (2.0*PSRC(:,IN-1,:) + 5.0*PSRC(:,IN,:) - PSRC(:,IN+1,:)) ! Flux IN-1
  ZFPOS3(:,IN,:)   = 1./6 * (2.0*PSRC(:,IN,:) + 5.0*PSRC(:,IN+1,:) - PSRC(:,IN+2,:)) ! Flux IN
@@ -2772,12 +2852,14 @@ IF(LNORTH_ll()) THEN
  ZBNEG2(:,IN,:)   = 13./12 * (PSRC(:,IN,:) - 2.0*PSRC(:,IN+1,:) + PSRC(:,IN+2,:))**2 &
       + 1./4   * (PSRC(:,IN,:) -                      PSRC(:,IN+2,:))**2 ! Smoothness indicator IN
  ZOMN2(:,IN-1:IN,:) = 3./5. / (ZEPS + ZBNEG2(:,IN-1:IN,:))**2 ! Non-normalized weight IN-1,IN
+!$acc end kernels
 !
  ELSE ! South boundary is proc border, with NHALO < 3 on north side
   call Print_msg(NVERB_FATAL,'GEN','ADVEC_WENO_K_3_VY','WENO5/CYCL fluxes calculation needs JPHEXT (&NHALO) >= 3 on north side')
  ENDIF
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(:,IN-1,:) = 1./6. * (2.0*PSRC(:,IN-3,:) - 7.0*PSRC(:,IN-2,:) + 11.0*PSRC(:,IN-1,:)) ! Flux IN-1
  ZFPOS1(:,IN,:)   = 1./6. * (2.0*PSRC(:,IN-2,:) - 7.0*PSRC(:,IN-1,:) + 11.0*PSRC(:,IN,:)) ! Flux IN
  ZBPOS1(:,IN-1,:) = 13./12. * (PSRC(:,IN-3,:) - 2.0*PSRC(:,IN-2,:) +     PSRC(:,IN-1,:))**2 & 
@@ -2814,6 +2896,7 @@ IF(LNORTH_ll()) THEN
                        + ZOMN2(:,IN-1:IN,:)/(ZOMN1(:,IN-1:IN,:)+ZOMN2(:,IN-1:IN,:)+ZOMN3(:,IN-1:IN,:)) * ZFNEG2(:,IN-1:IN,:) &
                        + ZOMN3(:,IN-1:IN,:)/(ZOMN1(:,IN-1:IN,:)+ZOMN2(:,IN-1:IN,:)+ZOMN3(:,IN-1:IN,:)) * ZFNEG3(:,IN-1:IN,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IN-1:IN,:)))
+!$acc end kernels
 !
 !
  CASE ('OPEN','WALL','NEST') 
@@ -2821,6 +2904,7 @@ IF(LNORTH_ll()) THEN
  ! Open, or Wall, or Nest boundary condition => WENO order reduction
  !---------------------------------------------------------------------------
 !
+!$acc kernels
  ! WENO scheme order 1, IN
     PR(:,IN,:) = PSRC(:,IN,:) * (0.5+SIGN(0.5,PRVCT(:,IN,:))) + &
                  PSRC(:,IN+1,:) * &
@@ -2848,7 +2932,8 @@ IF(LNORTH_ll()) THEN
                  (ZOMP2(:,IN-1,:)/(ZOMP1(:,IN-1,:)+ZOMP2(:,IN-1,:))*ZFPOS2(:,IN-1,:) + &
                    (ZOMP1(:,IN-1,:)/(ZOMP1(:,IN-1,:)+ZOMP2(:,IN-1,:))*ZFPOS1(:,IN-1,:))) &
       * (0.5+SIGN(0.5,PRVCT(:,IN-1,:)))  ! Total flux
-! 
+!$acc end kernels
+!
  END SELECT ! SELECT CASE (HLBCY(2)) ! Y direction LBC type on north side
 !
 ELSE
@@ -2865,7 +2950,8 @@ ELSE
 ! 
  ! ----- Positive fluxes -----
 !
- ! First positive stencil, needs indices i-2, i-1, i 
+!$acc kernels
+ ! First positive stencil, needs indices i-2, i-1, i
  ZFPOS1(:,IN-1,:) = 1./6. * (2.0*PSRC(:,IN-3,:) - 7.0*PSRC(:,IN-2,:) + 11.0*PSRC(:,IN-1,:)) ! Flux IN-1
  ZFPOS1(:,IN,:)   = 1./6. * (2.0*PSRC(:,IN-2,:) - 7.0*PSRC(:,IN-1,:) + 11.0*PSRC(:,IN,:)) ! Flux IN
  ZBPOS1(:,IN-1,:) = 13./12. * (PSRC(:,IN-3,:) - 2.0*PSRC(:,IN-2,:) +     PSRC(:,IN-1,:))**2 & 
@@ -2931,12 +3017,14 @@ ELSE
                        + ZOMN2(:,IN-1:IN,:)/(ZOMN1(:,IN-1:IN,:)+ZOMN2(:,IN-1:IN,:)+ZOMN3(:,IN-1:IN,:)) * ZFNEG2(:,IN-1:IN,:) &
                        + ZOMN3(:,IN-1:IN,:)/(ZOMN1(:,IN-1:IN,:)+ZOMN2(:,IN-1:IN,:)+ZOMN3(:,IN-1:IN,:)) * ZFNEG3(:,IN-1:IN,:)) &
                       * (0.5-SIGN(0.5,PRVCT(:,IN-1:IN,:)))
-! 
+!$acc end kernels
+!
  END IF ! NHALO
 !
 END IF ! IF(LNORTH_ll()) 
 !-------------------------------------------------------------------------------
 !
+!$acc kernels
 PR = PR * PRVCT ! Add contravariant flux
 !$acc end kernels
 !