-
Notifications
You must be signed in to change notification settings - Fork 5
/
main.f90
137 lines (115 loc) · 4.88 KB
/
main.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
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
!
! Copyright (C) 2013, Northwestern University
! See COPYRIGHT notice in top-level directory.
!
!----< main >-----------------------------------------------------
program main
use mpi
use param_m, only: npx, npy, npz
use param_m, only: initialize_param
use topology_m, only: gcomm, npes, myid, initialize_topology
implicit none
integer err
logical isArgvRight
call MPI_Init(err)
call MPI_Comm_rank(MPI_COMM_WORLD, myid, err)
call MPI_Comm_size(MPI_COMM_WORLD, npes, err)
call MPI_Comm_dup(MPI_COMM_WORLD, gcomm,err)
call read_command_line_arg(isArgvRight)
if (.NOT. isArgvRight) goto 999
! initialize parameters: nx, ny, nz, nsc, n_spec
call initialize_param(myid, gcomm)
! initialize MPI process topology
call initialize_topology(npx,npy,npz)
! main computation task is here
call MPI_Barrier(gcomm,err)
call solve_driver
999 call MPI_Comm_free(gcomm,err)
call MPI_Finalize(err)
end program main
!----< read_command_line_arg >------------------------------------
subroutine read_command_line_arg(isArgvRight)
use mpi
use param_m, only: nx_g, ny_g, nz_g, npx, npy, npz, nsc
use param_m, only: initialize_param
use runtime_m, only: method, restart, io_one_species_at_a_time
use topology_m, only: gcomm, npes, myid, initialize_topology
use io_profiling_m, only: dir_path
implicit none
character(len=128) executable
logical isArgvRight
! declare external functions
integer IARGC
! local variables for reading command-line arguments
character(len = 256) :: argv(9)
integer i, argc, int_argv(7), err
integer(MPI_OFFSET_KIND) io_size
! Only root process reads command-line arguments
if (myid .EQ. 0) then
isArgvRight = .TRUE.
call getarg(0, executable)
argc = IARGC()
if (argc .NE. 9) then
print *, 'Usage: ',trim(executable), &
' nx_g ny_g nz_g npx npy npz method restart dir_path'
isArgvRight = .FALSE.
else
do i=1, argc-2
call getarg(i, argv(i))
read(argv(i), FMT='(I16)') int_argv(i)
enddo
call getarg(argc-1, argv(argc-1))
read(argv(argc-1), FMT='(L)') restart
call getarg(argc, argv(argc))
dir_path = argv(argc)
nx_g = int_argv(1)
ny_g = int_argv(2)
nz_g = int_argv(3)
npx = int_argv(4)
npy = int_argv(5)
npz = int_argv(6)
method = int_argv(7)
endif
endif
! broadcast if arguments are valid
call MPI_Bcast(isArgvRight, 1, MPI_LOGICAL, 0, gcomm, err)
if (.NOT. isArgvRight) return
call MPI_Bcast(nx_g, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(ny_g, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(nz_g, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(npx, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(npy, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(npz, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(method, 1, MPI_INTEGER, 0, gcomm, err)
call MPI_Bcast(restart, 1, MPI_LOGICAL, 0, gcomm, err)
call MPI_Bcast(dir_path, 256, MPI_CHARACTER, 0, gcomm, err)
io_size = 8
io_size = io_size * nx_g
io_size = io_size * ny_g
io_size = io_size * ny_g
io_size = io_size / npes
if (io_size .GT. 2147483647) then
if (myid .EQ. 0) then
print*, '******** Error ********'
print*, ' Array size per process is too large for 4-byte integers'
print*, ' Please use a smaller array size. Exit...'
print*, '******** Error ********'
endif
call MPI_Finalize(err)
STOP
endif
io_one_species_at_a_time = .FALSE.
io_size = io_size * (11 + 3 + 2)
if (io_size .GT. 2147483647) then
if (myid .EQ. 0) then
print*, '******** Warning ********'
print*, 'Warning: Array size is too large for 4-byte integers'
print*, 'Warning: I/O is now performed one species at a time'
if (method .EQ. 1) &
print*, 'Warning: Switch to blocking I/O method'
print*, '******** Warning ********'
endif
method = 0
io_one_species_at_a_time = .TRUE.
endif
end subroutine read_command_line_arg