FIXME : Add documentation
!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.0 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 1.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 2.0 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 2.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 2.1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! 2.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.4 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.5 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(standard_header_type), | intent(in), | optional | :: | header |
Header for files with build and run information |
subroutine interactive(header)
use species, only: spec, nspec, has_electron_species
use geometry, only: beta_prime_input, bishop
use run_parameters, only: beta, fapar, fbpar
use standard_header, only: standard_header_type
use file_utils, only: run_name
use warning_helpers, only: is_zero
!> Header for files with build and run information
type(standard_header_type), intent(in), optional :: header
! Actual value for optional `header` input
type(standard_header_type) :: local_header
character(100) :: pythonin
integer :: sel, nbeta, j, ise, bishop_save, is
real :: beta_low, beta_high, dbeta, beta_save, alt, aln, fac, beta_prime_save
real :: fapar_save, fbpar_save, pri, pe, alpi, tpe_save, ptot, alp, dbdr
real, dimension (:), allocatable :: tp_save, fp_save
character (500) :: tag1, tag2
logical, save :: first = .true.
pythonin = "."//trim(run_name)//".pythonin"
if (first) then
if (present(header)) then
local_header = header
else
local_header = standard_header_type()
end if
open (newunit=interactive_record, file='.'//trim(run_name)//".record")
first = .false.
if (.not. stdin) then
open (newunit=interactive_input, file=trim(pythonin))
else
interactive_input = 5
end if
end if
call tell ('Interactive specification of a parameter scan')
100 continue
call text
call text ('Choose a parameter that you would like to vary (1-6):')
call text ('(1) beta (4) temperature gradient')
call text ('(2) beta_prime (5) density gradient')
call text ('(3) collisionality (6) Z_effective')
call text
call get_choice (6, sel)
select case (sel)
case default
call tell ('Try again. Choose an integer between 1 and 6, inclusively.')
goto 100
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.0 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (1)
call tell ('You have chosen to vary beta.')
101 continue
call text
call text ('Choose from the following:')
call text ('(1) Vary beta self-consistently')
call text ('(2) Vary beta with all other parameters held fixed (not self-consistently).')
call text
call get_choice (2, sel)
select case (sel)
case default
call tell ('Try again. Choose an integer between 1 and 2, inclusively.')
goto 101
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (1)
call tell ('You have chosen to vary beta self-consistently.')
102 continue
call text
call text ('Choose from the following:')
call text ('(1) Hold beta_prime fixed, vary electron temperature gradient scale length')
call text ('(2) Hold beta_prime fixed, vary all temperature gradient scale lengths by same factor')
call text ('(3) Hold beta_prime fixed, vary all density gradient scale lengths by same factor')
call text
call get_choice (3, sel)
select case (sel)
case default
call tell ('Try again. Choose an integer between 1 and 2, inclusively.')
goto 102
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (1)
call tell ('You have chosen to vary beta and electron temperature gradient at fixed beta_prime.')
call beta_range_low (beta_low, 'le', 0.)
call beta_range_high (beta_high, 'le', beta_low)
call num_runs (nbeta)
call tell ('Preparing a self-consistent beta scan at fixed beta_prime.', &
'The electron temperature gradient scale length will be varied', &
'to maintain consistency.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_min = ",e17.10,&
&" and beta_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
ptot = 0.
alp = 0.
pri = 0.
pe = 0.
alpi = 0.
ise = 0
do is=1,nspec
if (spec(is)%type == 2) then
pe = spec(is)%dens * spec(is)%temp
ise = is
else
pri = pri + spec(is)%dens * spec(is)%temp
alpi = alpi + spec(is)%dens * spec(is)%temp *(spec(is)%fprim + spec(is)%tprim)
endif
ptot = ptot + spec(is)%dens * spec(is)%temp
alp = alp + spec(is)%dens * spec(is)%temp *(spec(is)%fprim + spec(is)%tprim)
end do
if (.not. has_electron_species(spec)) call tell ('You really should use electrons for electromagnetic runs.')
alp = alp/ptot
dbdr = - beta*ptot*alp
dbeta = (beta_high-beta_low)/(nbeta-1)
do j = sel, sel+nbeta-1
beta_save = beta
beta = beta_low + (j - sel)*dbeta
tpe_save = spec(ise)%tprim
spec(ise)%tprim = - (spec(ise)%fprim + alpi/pe + dbdr/beta/pe)
write (tag1, fmt='("Varying beta and L_Te self-consistently with&
& beta_prime fixed")')
write (tag2, fmt='("beta = ",e17.10," and electron tprim = ",e17.10)') beta, spec(ise)%tprim
call write_namelists (j, tag1, tag2, local_header)
spec(ise)%tprim = tpe_save
end do
beta = beta_save
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (2)
call tell ('You have chosen to vary beta and all temperature &
&gradient scale lengths together at fixed beta_prime.')
call beta_range_low (beta_low, 'le', 0.)
call beta_range_high (beta_high, 'le', beta_low)
call num_runs (nbeta)
call tell ('Preparing a self-consistent beta scan at fixed beta_prime.', &
'All temperature gradient scale lengths will be varied', &
'by the same factor to maintain consistency.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_min = ",e17.10,&
&" and beta_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
allocate (tp_save (nspec))
ptot = 0.
alt = 0.
aln = 0.
do is=1,nspec
ptot = ptot + spec(is)%dens * spec(is)%temp
alt = alt + spec(is)%dens * spec(is)%temp *(spec(is)%tprim)
aln = aln + spec(is)%dens * spec(is)%temp *(spec(is)%fprim)
end do
if (.not. has_electron_species(spec)) call tell ('You really should use electrons for electromagnetic runs.')
alp = (alt+aln)/ptot
dbdr = - beta*ptot*alp
dbeta = (beta_high-beta_low)/(nbeta-1)
do j = sel, sel+nbeta-1
beta_save = beta
beta = beta_low + (j - sel)*dbeta
fac = -(dbdr/beta+aln)/alt
tp_save = spec%tprim
spec%tprim = fac*spec%tprim
write (tag1, fmt='("Varying beta and all L_T values self-consistently")')
write (tag2, fmt='("beta = ",e17.10," and tprim values scaled by ",e17.10)') beta, fac
call write_namelists (j, tag1, tag2, local_header)
spec%tprim = tp_save
end do
beta = beta_save
deallocate (tp_save)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.1.3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (3)
call tell ('You have chosen to vary beta and all density &
&gradient scale lengths together at fixed beta_prime.')
call beta_range_low (beta_low, 'le', 0.)
call beta_range_high (beta_high, 'le', beta_low)
call num_runs (nbeta)
call tell ('Preparing a self-consistent beta scan at fixed beta_prime.', &
'All density gradient scale lengths will be varied', &
'by the same factor to maintain consistency.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_min = ",e17.10,&
&" and beta_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
allocate (fp_save (nspec))
ptot = 0.
alt = 0.
aln = 0.
do is=1,nspec
ptot = ptot + spec(is)%dens * spec(is)%temp
alt = alt + spec(is)%dens * spec(is)%temp *(spec(is)%tprim)
aln = aln + spec(is)%dens * spec(is)%temp *(spec(is)%fprim)
end do
if (.not. has_electron_species(spec)) call tell ('You really should use electrons for electromagnetic runs.')
alp = (alt+aln)/ptot
dbdr = - beta*ptot*alp
dbeta = (beta_high-beta_low)/(nbeta-1)
do j = sel, sel+nbeta-1
beta_save = beta
beta = beta_low + (j - sel)*dbeta
fac = -(dbdr/beta+alt)/aln
fp_save = spec%fprim
spec%fprim = fac*spec%fprim
write (tag1, fmt='("Varying beta and all L_n values self-consistently")')
write (tag2, fmt='("beta = ",e17.10," and tprim values scaled by ",e17.10)') beta, fac
call write_namelists (j, tag1, tag2, local_header)
spec%fprim = fp_save
end do
beta = beta_save
deallocate (fp_save)
end select
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (2)
call tell ('You have selected to vary beta non-self-consistently.')
call beta_range_low (beta_low, 'lt', 0.)
call beta_range_high (beta_high, 'le', beta_low)
call num_runs (nbeta)
call tell ('Preparing a non-self-consistent beta scan.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_min = ",e17.10,&
&" and beta_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
dbeta = (beta_high-beta_low)/(nbeta-1)
do j = sel, sel+nbeta-1
beta_save = beta
fapar_save = fapar
fbpar_save = fbpar
beta = beta_low + (j - sel)*dbeta
if (is_zero(beta)) then
fapar = 0.
fbpar = 0.
else
if (is_zero(fapar) .and. is_zero(fbpar)) then
fapar = 1.0 ; fbpar = 1.0
end if
end if
write (tag1, fmt='("Varying beta, all else fixed")')
write (tag2, fmt='("beta = ",e17.10)') beta
call write_namelists (j, tag1, tag2, local_header)
fapar = fapar_save
fbpar = fbpar_save
beta = beta_save
end do
end select
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2.0 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (2) ! beta_prime
call tell ('You have chosen to vary beta_prime.')
115 continue
call text
call text ('Choose from the following:')
call text ('(1) Vary beta_prime self-consistently')
call text ('(2) Vary beta_prime with ALL other parameters held fixed (non-self-consistently).')
call text
call get_choice (2, sel)
select case (sel)
case default
call tell ('Try again. Choose an integer between 1 and 2, inclusively.')
goto 115
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (1)
call tell ('You have chosen to vary beta_prime self-consistently.')
116 continue
call text
call text ('Choose from the following:')
call text ('(1) Hold gradient scale lengths fixed, vary beta')
call text
call get_choice (1, sel)
select case (sel)
case default
call tell ('Try again. Choose an integer between 1 and 1, inclusively.')
goto 116
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2.1.1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (1)
call tell ('You have chosen to vary beta_prime while holding gradient scale lengths fixed.')
call beta_prime_range_low (beta_low)
call beta_prime_range_high (beta_high, beta_low)
call num_runs (nbeta)
call tell ('Preparing a self-consistent beta_prime scan.', &
'Beta will be varied to maintain consistency.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_prime_min = ",e17.10,&
&" and beta_prime_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
ptot = 0.
alp = 0.
do is=1,nspec
ptot = ptot + spec(is)%dens * spec(is)%temp
alp = alp + spec(is)%dens * spec(is)%temp *(spec(is)%fprim + spec(is)%tprim)
end do
alp = alp/ptot
dbdr = - beta*ptot*alp
if (is_zero(alp)) then
call tell ('Cannot proceed, because Lp = infinity', &
'No input files for scan written')
return
end if
beta_save = beta
beta_prime_save = dbdr
fac = -1./(ptot*alp)
dbeta = (beta_high-beta_low)/(nbeta-1) ! actually, this is dbeta_prime
do j = sel, sel+nbeta-1
beta_prime_save = beta_prime_input
beta_prime_input = beta_low + (j - sel)*dbeta
beta_save = beta
beta = beta_prime_input*fac
fapar_save = fapar ; fbpar_save = fbpar
if (is_zero(beta)) then
fapar = 0. ; fbpar = 0.
else
if (is_zero(fapar) .and. is_zero(fbpar)) then
fapar = 1.0 ; fbpar = 1.0
end if
end if
select case (bishop)
case default
bishop_save = bishop
bishop = 6
case (4)
! nothing, continue to use bishop = 4
end select
write (tag1, fmt='("Varying beta_prime and beta self-consistently")')
write (tag2, fmt='("beta_prime = ",e17.10," and beta = ",e17.10)') beta_prime_input, beta
call write_namelists (j, tag1, tag2, local_header)
fapar = fapar_save
fbpar = fbpar_save
beta = beta_save
beta_prime_input = beta_prime_save
select case (bishop)
case default
bishop = bishop_save
case (4)
! nothing, continue to use bishop = 4
end select
end do
end select
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2.2 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (2)
call tell ('You have selected to vary beta_prime non-self-consistently.')
call beta_prime_range_low (beta_low)
call beta_prime_range_high (beta_high, beta_low)
call num_runs (nbeta)
call tell ('Preparing a non-self-consistent beta_prime scan.')
call run_number (sel, nbeta)
write (tag1, fmt='(i3," runs prepared with beta_prime_min = ",e17.10,&
&" and beta_prime_max = ",e17.10)') nbeta, beta_low, beta_high
write (tag2, fmt='("Files are numbered from ",i3," to ",i3)') sel, sel+nbeta-1
call tell (tag1, tag2)
dbeta = (beta_high-beta_low)/(nbeta-1)
do j = sel, sel+nbeta-1
beta_prime_save = beta_prime_input
beta_prime_input = beta_low + (j - sel)*dbeta
select case (bishop)
case default
bishop_save = bishop
bishop = 6
case (4)
! nothing, continue to use bishop = 4
end select
write (tag1, fmt='("Varying beta_prime only (non-self-consistently)")')
write (tag2, fmt='("beta_prime = ",e17.10)') beta_prime_input
call write_namelists (j, tag1, tag2, local_header)
beta_prime_input = beta_prime_save
select case (bishop)
case default
bishop = bishop_save
case (4)
! nothing, continue to use bishop = 4
end select
end do
end select
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (3) ! collisionality
call tell ('You have chosen to vary collisionality.')
call text ('Not yet implemented (sorry).')
call text
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.4 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (4) ! temperature gradient
call tell ('You have chosen to vary temperature gradient.')
call text ('Not yet implemented (sorry).')
call text
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.5 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (5) ! density gradient
call tell ('You have chosen to vary density gradient.')
call text ('Not yet implemented (sorry).')
call text
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 1.6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
case (6) ! Z_effective
call tell ('You have chosen to vary Z_effective.')
call text ('Not yet implemented (sorry).')
call text
end select
end subroutine interactive