-
Notifications
You must be signed in to change notification settings - Fork 3
/
pack.f90
96 lines (74 loc) · 2.81 KB
/
pack.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
MODULE pack_module
USE definitions_module
USE pack_kernel_module
USE report_module
CONTAINS
SUBROUTINE tea_pack_buffers( fields, depth, face, mpi_buffer, offsets)
IMPLICIT NONE
INTEGER :: fields(:),depth
INTEGER :: offsets(:)
REAL(KIND=8) :: mpi_buffer(:)
INTEGER :: face
CALL call_packing_functions( fields, depth, face, .TRUE., mpi_buffer, offsets)
END SUBROUTINE
SUBROUTINE tea_unpack_buffers( fields, depth, face, mpi_buffer, offsets)
IMPLICIT NONE
INTEGER :: fields(:),depth
INTEGER :: offsets(:)
REAL(KIND=8) :: mpi_buffer(:)
INTEGER :: face
CALL call_packing_functions( fields, depth, face, .FALSE., mpi_buffer, offsets)
END SUBROUTINE
SUBROUTINE call_packing_functions( fields, depth, face, packing, mpi_buffer, offsets)
IMPLICIT NONE
INTEGER :: fields(:),depth
INTEGER :: offsets(:)
REAL(KIND=8) :: mpi_buffer(:)
INTEGER :: face,t,tile_offset
LOGICAL :: packing
!$OMP PARALLEL PRIVATE(tile_offset)
!$OMP DO
DO t=1,tiles_per_task
SELECT CASE (face)
CASE (CHUNK_LEFT, CHUNK_RIGHT)
tile_offset = (chunk%tiles(t)%bottom - chunk%bottom)*depth
CASE (CHUNK_BOTTOM, CHUNK_TOP)
tile_offset = (chunk%tiles(t)%left - chunk%left)*depth
IF (tile_offset .NE. 0) THEN
tile_offset = tile_offset + depth*depth
ENDIF
CASE DEFAULT
CALL report_error("pack.f90","Invalid face pased to buffer packing")
END SELECT
IF (chunk%tiles(t)%tile_neighbours(face) .NE. EXTERNAL_FACE) THEN
CYCLE
ENDIF
CALL pack_all(chunk%tiles(t)%field%x_min, &
chunk%tiles(t)%field%x_max, &
chunk%tiles(t)%field%y_min, &
chunk%tiles(t)%field%y_max, &
chunk%halo_exchange_depth, &
chunk%tiles(t)%tile_neighbours, &
chunk%tiles(t)%field%density, &
chunk%tiles(t)%field%energy0, &
chunk%tiles(t)%field%energy1, &
chunk%tiles(t)%field%u, &
chunk%tiles(t)%field%vector_p, &
chunk%tiles(t)%field%vector_sd, &
chunk%tiles(t)%field%vector_rtemp, &
chunk%tiles(t)%field%vector_z, &
chunk%tiles(t)%field%vector_kx, &
chunk%tiles(t)%field%vector_ky, &
chunk%tiles(t)%field%vector_di, &
fields, &
depth, &
face, &
packing, &
mpi_buffer, &
offsets, &
tile_offset)
ENDDO
!$OMP END DO NOWAIT
!$OMP END PARALLEL
END SUBROUTINE
END MODULE