PB3D  [2.45]
Ideal linear high-n MHD stability in 3-D
input_utilities.f90
Go to the documentation of this file.
1 !------------------------------------------------------------------------------!
3 !------------------------------------------------------------------------------!
5 #include <PB3D_macros.h>
6  use str_utilities
7  use output_ops
8  use messages
9  use num_vars, only: dp, max_str_ln
10 
11  implicit none
12  private
14 
15 contains
21  function get_log(yes,ind) result(val)
22  use num_vars, only: rank
23  use mpi_utilities, only: broadcast_var
24 
25  ! input / output
26  logical :: val
27  logical :: yes
28  logical, intent(in), optional :: ind
29 
30  ! local variables
31  character(len=11) :: empty_str = '' ! empty string
32  character(len=max_str_ln) :: answer_str ! string with answer
33  integer :: istat ! status
34  logical :: ind_loc ! local version of ind
35 
36  ! set local ind
37  ind_loc = .false.
38  if (present(ind)) ind_loc = ind
39 
40  ! only master can receive input
41  if (rank.eq.0) then
42  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
43  if (yes) then
44  write(*,'(A)',advance='no') 'y(es)/n(o) [yes]: '
45  val = .true.
46  else
47  write(*,'(A)',advance='no') 'y(es)/n(o) [no]: '
48  val = .false.
49  end if
50  call stop_time
51  read (*, '(A)') answer_str
52  call start_time
53 
54  select case (strh2l(trim(answer_str)))
55  !case ('y','yes')
56  case ('y','Y','yes','Yes','YEs','YES','yEs','yES','yeS','YeS')
57  val = .true.
58  case ('n','N','no','No','NO','nO')
59  val = .false.
60  end select
61  end if
62 
63  ! if not individual, broadcast result
64  if (.not.ind_loc) then
65  istat = broadcast_var(val)
66  if (istat.ne.0) call writo('In get_log, something went wrong. &
67  &Default used.',warning=.true.)
68  end if
69  end function get_log
70 
76  function get_real(lim_lo,lim_hi,ind) result(val)
77  use num_vars, only: rank
78  use mpi_utilities, only: broadcast_var
79 
80  ! input / output
81  real(dp) :: val
82  real(dp), intent(in), optional :: lim_lo
83  real(dp), intent(in), optional :: lim_hi
84  logical, intent(in), optional :: ind
85 
86  ! local variables
87  character(len=11) :: empty_str = '' ! empty string
88  integer :: istat ! status
89  logical :: ind_loc ! local version of ind
90  real(dp) :: lims_loc(2) ! local version of limits
91 
92  ! set local ind
93  ind_loc = .false.
94  if (present(ind)) ind_loc = ind
95 
96  ! initialize val
97  val = 0._dp
98 
99  ! only master can receive input
100  if (rank.eq.0) then
101  ! set up local limits
102  lims_loc = [-huge(1._dp),huge(1._dp)]
103  if (present(lim_lo)) lims_loc(1) = lim_lo
104  if (present(lim_hi)) lims_loc(2) = lim_hi
105 
106  ! get input
107  do
108  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
109  write(*,'(A)',advance='no') 'Input a value'
110  if (present(lim_lo).or.present(lim_hi)) then
111  write(*,'(A)',advance='no') ' ['
112  if (present(lim_lo)) write(*,'(A)',advance='no') &
113  &trim(r2strt(lim_lo))
114  write(*,'(A)',advance='no') '..'
115  if (present(lim_hi)) write(*,'(A)',advance='no') &
116  &trim(r2strt(lim_hi))
117  write(*,'(A)',advance='no') ']'
118  end if
119  write(*,'(A)',advance='no') ': '
120  call stop_time
121  read (*,*,iostat=istat) val
122  call start_time
123 
124  if (istat.ne.0 .or. val.lt.lims_loc(1) .or. val.gt. &
125  &lims_loc(2)) then
126  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
127  write(*,'(A)',advance='no') 'Choose a value between '//&
128  &trim(r2strt(lims_loc(1)))//' and '//&
129  &trim(r2strt(lims_loc(2)))
130  write(*,*) ''
131  cycle
132  else
133  exit
134  end if
135  end do
136  end if
137 
138  ! if not individual, broadcast result
139  if (.not.ind_loc) then
140  istat = broadcast_var(val)
141  if (istat.ne.0) call writo('In get_real, something went &
142  &wrong. Default of zero used.',warning=.true.)
143  end if
144  end function get_real
145 
151  function get_int(lim_lo,lim_hi,ind) result(val)
152  use num_vars, only: rank
153  use mpi_utilities, only: broadcast_var
154 
155  ! input / output
156  integer :: val
157  integer, intent(in), optional :: lim_lo
158  integer, intent(in), optional :: lim_hi
159  logical, intent(in), optional :: ind
160 
161  ! local variables
162  character(len=11) :: empty_str = '' ! empty string
163  integer :: istat ! status
164  logical :: ind_loc ! local version of ind
165  integer :: lims_loc(2) ! local version of limits
166 
167  ! set local ind
168  ind_loc = .false.
169  if (present(ind)) ind_loc = ind
170 
171  ! initialize val
172  val = 0
173 
174  ! only master can receive input
175  if (rank.eq.0) then
176  ! set up local limits
177  lims_loc = [-huge(1),huge(1)]
178  if (present(lim_lo)) lims_loc(1) = lim_lo
179  if (present(lim_hi)) lims_loc(2) = lim_hi
180 
181  ! get input
182  do
183  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
184  write(*,'(A)',advance='no') 'Input a value'
185  if (present(lim_lo).or.present(lim_hi)) then
186  write(*,'(A)',advance='no') ' ['
187  if (present(lim_lo)) write(*,'(A)',advance='no') &
188  &trim(i2str(lim_lo))
189  write(*,'(A)',advance='no') '..'
190  if (present(lim_hi)) write(*,'(A)',advance='no') &
191  &trim(i2str(lim_hi))
192  write(*,'(A)',advance='no') ']'
193  end if
194  write(*,'(A)',advance='no') ': '
195  call stop_time
196  read (*,*,iostat=istat) val
197  call start_time
198 
199  if (istat.ne.0 .or. val.lt.lims_loc(1) .or. val.gt. &
200  &lims_loc(2)) then
201  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
202  write(*,'(A)',advance='no') 'Choose a value between '//&
203  &trim(i2str(lims_loc(1)))//' and '//&
204  &trim(i2str(lims_loc(2)))
205  write(*,*) ''
206  cycle
207  else
208  exit
209  end if
210  end do
211  end if
212 
213  ! if not individual, broadcast result
214  if (.not.ind_loc) then
215  istat = broadcast_var(val)
216  if (istat.ne.0) call writo('In get_int, something went &
217  &wrong. Default of zero used.',warning=.true.)
218  end if
219  end function get_int
220 
225  subroutine pause_prog(ind)
227  use num_vars, only: rank, rank
228 
229  ! input / output
230  logical, intent(in), optional :: ind ! individual pause or not
231 
232  ! local variables
233  character(len=11) :: empty_str = '' ! empty string
234  integer :: istat ! status
235  logical :: ind_loc ! local version of ind
236  character(len=max_str_ln) :: hidden_msg ! hidden message
237 
238  ! output message
239  if (rank.eq.0) then
240  write(*,'(A)',advance='no') empty_str ! first print empty string so that output is visible
241  write(*,'(A)',advance='no') 'Paused. Press enter...'
242  end if
243 
244  ! set local ind
245  ind_loc = .false.
246  if (present(ind)) ind_loc = ind
247 
248  ! only master can receive input
249  if (rank.eq.0) then
250  call stop_time
251  read (*,'(A)') hidden_msg
252  call start_time
253  end if
254 
255  ! wait for MPI
256  if (.not.ind_loc) then
257  istat = wait_mpi()
258  if (istat.ne.0) call writo('In pause_prog, something went &
259  &wrong. Continuing.',warning=.true.)
260  end if
261 
262  ! hidden message
263  if (trim(hidden_msg).eq.'stop') stop 0
264  end subroutine pause_prog
265 
267  subroutine dealloc_in()
268  use num_vars, only: eq_style
269  use vmec_vars, only: dealloc_vmec
270  use helena_vars, only: dealloc_hel
271 
272  ! deallocate depending on equilibrium style
273  select case (eq_style)
274  case (1) ! VMEC
275  call dealloc_vmec
276  case (2) ! HELENA
277  call dealloc_hel
278  end select
279  end subroutine dealloc_in
280 end module input_utilities
input_utilities::get_real
real(dp) function, public get_real(lim_lo, lim_hi, ind)
Queries for user input for a real value, where allowable range can be provided as well.
Definition: input_utilities.f90:77
num_vars::dp
integer, parameter, public dp
double precision
Definition: num_vars.f90:46
mpi_utilities
Numerical utilities related to MPI.
Definition: MPI_utilities.f90:20
num_vars
Numerical variables used by most other modules.
Definition: num_vars.f90:4
input_utilities::get_log
logical function, public get_log(yes, ind)
Queries for a logical value yes or no, where the default answer is also to be provided.
Definition: input_utilities.f90:22
num_vars::max_str_ln
integer, parameter, public max_str_ln
maximum length of strings
Definition: num_vars.f90:50
vmec_vars::dealloc_vmec
subroutine, public dealloc_vmec()
Deallocates VMEC quantities that are not used anymore.
Definition: VMEC_vars.f90:57
str_utilities::i2str
elemental character(len=max_str_ln) function, public i2str(k)
Convert an integer to string.
Definition: str_utilities.f90:18
messages::start_time
subroutine, public start_time()
Start a timer.
Definition: messages.f90:121
messages::stop_time
subroutine, public stop_time()
Stop a timer.
Definition: messages.f90:132
str_utilities
Operations on strings.
Definition: str_utilities.f90:4
str_utilities::r2strt
elemental character(len=max_str_ln) function, public r2strt(k)
Convert a real (double) to string.
Definition: str_utilities.f90:54
str_utilities::strh2l
character(len(input_string)) function, public strh2l(input_string)
Convert a string to lowercase.
Definition: str_utilities.f90:109
num_vars::eq_style
integer, public eq_style
either 1 (VMEC) or 2 (HELENA)
Definition: num_vars.f90:89
helena_vars::dealloc_hel
subroutine, public dealloc_hel
Deallocates HELENA quantities that are not used any more.
Definition: HELENA_vars.f90:41
mpi_utilities::wait_mpi
integer function, public wait_mpi()
Wait for all processes, wrapper to MPI barrier.
Definition: MPI_utilities.f90:744
messages::writo
subroutine, public writo(input_str, persistent, error, warning, alert)
Write output to file identified by output_i.
Definition: messages.f90:275
messages
Numerical utilities related to giving output.
Definition: messages.f90:4
helena_vars
Variables that have to do with HELENA quantities.
Definition: HELENA_vars.f90:4
input_utilities::get_int
integer function, public get_int(lim_lo, lim_hi, ind)
Queries for user input for an integer value, where allowable range can be provided as well.
Definition: input_utilities.f90:152
input_utilities::pause_prog
subroutine, public pause_prog(ind)
Pauses the running of the program.
Definition: input_utilities.f90:226
vmec_vars
Variables that concern the output of VMEC.
Definition: VMEC_vars.f90:4
output_ops
Operations concerning giving output, on the screen as well as in output files.
Definition: output_ops.f90:5
num_vars::rank
integer, public rank
MPI rank.
Definition: num_vars.f90:68
input_utilities::dealloc_in
subroutine, public dealloc_in()
Cleans up input from equilibrium codes.
Definition: input_utilities.f90:268
input_utilities
Numerical utilities related to input.
Definition: input_utilities.f90:4
mpi_utilities::broadcast_var
Wrapper function to broadcast a single variable using MPI.
Definition: MPI_utilities.f90:87