forked from claw-project/claw-compiler
-
Notifications
You must be signed in to change notification settings - Fork 1
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add test case for call-site collapse in sca foward
- Loading branch information
1 parent
7c82bf7
commit 339eaa5
Showing
3 changed files
with
116 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |