Skip to content

Commit

Permalink
Add test case for call-site collapse in sca foward
Browse files Browse the repository at this point in the history
  • Loading branch information
clementval committed Oct 24, 2018
1 parent 7c82bf7 commit 339eaa5
Show file tree
Hide file tree
Showing 3 changed files with 116 additions and 0 deletions.
30 changes: 30 additions & 0 deletions test/claw/sca/sca43/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
!
! This file is released under terms of BSD license
! See LICENSE file for more information
!
! Test the CLAW abstraction model with one additional dimension.
!

PROGRAM test_abstraction16
USE mo_column_extra, ONLY: compute_one, compute_two
REAL, DIMENSION(20,60) :: q, t ! Fields as declared in the whole model
INTEGER :: nproma, nz ! Size of array fields
INTEGER :: p ! Loop index

nproma = 20
nz = 60

DO p = 1, nproma
q(p,1) = 0.0
t(p,1) = 0.0
END DO

!$claw parallelize forward create update
DO p = 1, nproma
CALL compute_one(nz, q(p,:), t(p,:))
CALL compute_two(nz, q(p,:), t(p,:))
END DO

PRINT*,SUM(q)
PRINT*,SUM(t)
END PROGRAM test_abstraction16
45 changes: 45 additions & 0 deletions test/claw/sca/sca43/mo_column.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
!
! This file is released under terms of BSD license
! See LICENSE file for more information
!

MODULE mo_column
IMPLICIT NONE

TYPE ty_column

CONTAINS
PROCEDURE :: compute_column
END TYPE ty_column

CONTAINS

! Compute only one column
SUBROUTINE compute_column(this, nz, q, t)
IMPLICIT NONE

CLASS(ty_column) :: this
INTEGER, INTENT(IN) :: nz ! Size of the array field
REAL, INTENT(INOUT) :: t(:) ! Field declared as one column only
REAL, INTENT(INOUT) :: q(:) ! Field declared as one column only
INTEGER :: k ! Loop index
REAL :: c ! Coefficient

! CLAW definition

! Define one dimension that will be added to the variables defined in the
! data clause.
! Apply the parallelization transformation on this subroutine.

!$claw define dimension proma(1:nproma) &
!$claw parallelize

c = 5.345
DO k = 2, nz
t(k) = c * k
q(k) = q(k - 1) + t(k) * c
END DO
q(nz) = q(nz) * c
END SUBROUTINE compute_column

END MODULE mo_column
41 changes: 41 additions & 0 deletions test/claw/sca/sca43/mo_column_extra.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
!
! This file is released under terms of BSD license
! See LICENSE file for more information
!

MODULE mo_column_extra
USE mo_column, ONLY: ty_column, compute_column
IMPLICIT NONE

CONTAINS

SUBROUTINE compute_one(nz, q, t)
IMPLICIT NONE

INTEGER, INTENT(IN) :: nz ! Size of the array field
REAL, INTENT(INOUT) :: t(:) ! Field declared as one column only
REAL, INTENT(INOUT) :: q(:) ! Field declared as one column only
TYPE(ty_column) :: column

!$claw parallelize forward
CALL column%compute_column(nz, q, t)

END SUBROUTINE compute_one

SUBROUTINE compute_two(nz, q, t)
IMPLICIT NONE

INTEGER, INTENT(IN) :: nz ! Size of the array field
REAL, INTENT(INOUT) :: t(:) ! Field declared as one column only
REAL, INTENT(INOUT) :: q(:) ! Field declared as one column only
TYPE(ty_column) :: column

!$claw define dimension proma(1:nproma) &
!$claw parallelize


q = q + sum(t)

END SUBROUTINE compute_two

END MODULE mo_column_extra

0 comments on commit 339eaa5

Please sign in to comment.