V3FIT
v3fit_input.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @header, @table_section, @table_subsection, @item and @end_table commands
3 ! are custom defined commands in Doxygen.in. They are defined under ALIASES.
4 ! For the page created here, the 80 column limit is exceeded. Arguments of
5 ! aliases are separated by ','. If you intended ',' to be a string you must use
6 ! an escaped comma '\,'.
7 !
550 !-------------------------------------------------------------------------------
551 !*******************************************************************************
554 !
555 ! Note separating the Doxygen comment block here so detailed decription is
556 ! found in the Module not the file.
557 !
569 !*******************************************************************************
570  MODULE v3fit_input
571  USE stel_kinds
572  USE data_parameters
573  USE combination
574  USE pprofile_t
575 
576  IMPLICIT NONE
577 
578 !*******************************************************************************
579 ! v3fit input module parameters
580 !*******************************************************************************
582  INTEGER, PARAMETER :: v3fit_max_diagnostics = 1000
584  INTEGER, PARAMETER :: v3fit_max_limiters = 1000
586  INTEGER, PARAMETER :: v3fit_max_priors = 1000
588  INTEGER, PARAMETER :: v3fit_max_combinations = 1000
590  INTEGER, PARAMETER :: v3fit_max_signals = v3fit_max_diagnostics &
591  & + v3fit_max_limiters &
592  & + v3fit_max_priors &
594  & + max_gaussprocess
595 
597  INTEGER, PARAMETER :: v3fit_max_parameters = 100
598 
607  INTEGER, PARAMETER :: v3fit_max_spec_size = 150
608 
610  INTEGER, PARAMETER :: v3fit_max_lif_size = 100
611 
613  INTEGER, PARAMETER :: v3fit_max_cos_size = 100
614 
616  INTEGER, PARAMETER :: v3fit_step_name_length = 4
617 
618 !*******************************************************************************
619 ! DERIVED-TYPE DECLARATIONS
620 ! 1) v3fit_namelist_class
621 !
622 !*******************************************************************************
625  CHARACTER (len=path_length) :: main_nli_filename = ''
626 
627 ! Equilibrium input files
629  CHARACTER (len=path_length) :: vmec_nli_filename = ''
631  CHARACTER (len=path_length) :: vmec_wout_input = ''
633  CHARACTER (len=path_length) :: vacuum_nli_filename = ''
635  CHARACTER (len=path_length) :: siesta_nli_filename = ''
637  CHARACTER (len=path_length) :: siesta_restart_filename = ''
638 
639 ! Signal input files
641  CHARACTER (len=path_length) :: mdsig_list_filename = ''
643  CHARACTER (len=path_length) :: sxrch_dot_filename = ''
646  CHARACTER (len=path_length) :: ipch_dot_filename = ''
648  CHARACTER (len=path_length) :: thscte_dot_filename = ''
650  CHARACTER (len=path_length) :: mse_dot_filename = ''
652  CHARACTER (len=path_length) :: ece_dot_filename = ''
654  CHARACTER (len=path_length) :: sxrem_ratio_dot_filename = ''
656  CHARACTER (len=path_length) :: limiter_grid_file = ''
657 
658 ! Array allocation sizes. These should be set to the maxmium size.
665 
666 ! Task specification and work variables
672  CHARACTER (len=data_name_length) :: my_task = ''
673 
674 ! Model profile specification
675 ! Electron Denisty
681  CHARACTER (len=p_type_len) :: pp_ne_ptype = 'none'
684  REAL (rprec), DIMENSION(ilb_b:iub_b) :: pp_ne_b = 0.0
687  REAL (rprec), DIMENSION(iub_asf) :: pp_ne_as = 0.0
690  REAL (rprec), DIMENSION(iub_asf) :: pp_ne_af = 0.0
691 
692 ! Soft x-ray emissvity
698  CHARACTER (len=p_type_len) :: pp_sxrem_ptype = 'none'
702  REAL (rprec), DIMENSION(ilb_b:iub_b) :: pp_sxrem_b = 0.0
706  REAL (rprec), DIMENSION(iub_asf) :: pp_sxrem_as = 0.0
710  REAL (rprec), DIMENSION(iub_asf) :: pp_sxrem_af = 0.0
711 
712 ! Multi soft x-ray emissvity profile specification.
714  INTEGER :: num_sxrem_p = 1
719  CHARACTER (len=p_type_len), DIMENSION(max_sxrem_profiles) &
720  & :: pp_sxrem_ptype_a = 'none'
721 
723  REAL (rprec), DIMENSION(max_sxrem_profiles,ilb_b:iub_b) &
724  & :: pp_sxrem_b_a = 0.0
725 
727  REAL (rprec), DIMENSION(max_sxrem_profiles,iub_asf) &
728  & :: pp_sxrem_as_a = 0.0
729 
731  REAL (rprec), DIMENSION(max_sxrem_profiles,iub_asf) &
732  & :: pp_sxrem_af_a = 0.0
733 
734 ! Electron temperature
740  CHARACTER (len=p_type_len) :: pp_te_ptype = 'none'
743  REAL (rprec), DIMENSION(ilb_b:iub_b) :: pp_te_b = 0.0
746  REAL (rprec), DIMENSION(iub_asf) :: pp_te_as = 0.0
749  REAL (rprec), DIMENSION(iub_asf) :: pp_te_af = 0.0
750 
751 ! Ion temperature
756  CHARACTER (len=p_type_len) :: pp_ti_ptype = 'none'
759  REAL (rprec), DIMENSION(ilb_b:iub_b) :: pp_ti_b = 0.0
762  REAL (rprec), DIMENSION(iub_asf) :: pp_ti_as = 0.0
765  REAL (rprec), DIMENSION(iub_asf) :: pp_ti_af = 0.0
766 
767 ! Effective charge
772  CHARACTER (len=p_type_len) :: pp_ze_ptype = 'none'
775  REAL (rprec), DIMENSION(ilb_b:iub_b) :: pp_ze_b = 0.0
778  REAL (rprec), DIMENSION(iub_asf) :: pp_ze_as = 0.0
781  REAL (rprec), DIMENSION(iub_asf) :: pp_ze_af = 0.0
782 
783 ! Soft X-ray emission ratio
785  REAL (rprec), DIMENSION(iub_asf) :: sxrem_te_a = 0.0
787  REAL (rprec), DIMENSION(iub_asf) :: sxrem_ratio_a = 0.0
788 
789 ! Model Specification Variables
791  CHARACTER (len=data_name_length) :: model_eq_type = 'vmec'
797  CHARACTER (len=data_name_length) :: model_ne_type = 'pp_ne'
801  CHARACTER (len=data_name_length) :: model_sxrem_type = 'none'
804  CHARACTER (len=data_name_length), &
805  & DIMENSION(max_sxrem_profiles) :: &
806  & model_sxrem_type_a = 'none'
807 
809  CHARACTER (len=data_name_length) :: model_te_type = 'none'
812  CHARACTER (len=data_name_length) :: model_ti_type = 'none'
815  CHARACTER (len=data_name_length) :: model_ze_type = 'none'
817  REAL (rprec) :: ne_pp_unit = 1.0e18
819  REAL (rprec) :: ne_min = 0.0
821  REAL (rprec) :: te_min = 0.0
823  REAL (rprec) :: ti_min = 0.0
825  REAL (rprec) :: ze_min = 1.0
827  REAL (rprec), DIMENSION(max_sxrem_profiles) :: sxrem_min = 0.0
829  REAL (rprec) :: e_pressure_fraction = 0.5
831  CHARACTER (len=data_name_length) :: emission_file = ''
833  REAL (rprec) :: ece_resonance_range = 0.0
835  REAL (rprec), DIMENSION(v3fit_max_parameters) :: coosig_wgts = 0.0
836 
837 ! Reconstruction constraints
839  INTEGER :: n_rc = 0
841  CHARACTER (len=data_name_length), &
842  & DIMENSION(v3fit_max_parameters) :: rc_type = ''
843 
844  INTEGER, &
845  & DIMENSION(v3fit_max_parameters) :: rc_index = 0
846 
847  REAL (rprec), &
848  & DIMENSION(v3fit_max_parameters) :: rc_value = 0.0
849 
850 ! Derived parameters
852  INTEGER :: n_dp = 0
854  CHARACTER (len=data_name_length), &
855  & DIMENSION(v3fit_max_parameters) :: dp_type = ''
856 
857  INTEGER, &
858  & DIMENSION(v3fit_max_parameters,2) :: dp_index = 0
859 
860 ! Reconstruction parameters
862  INTEGER :: n_rp = 0
864  CHARACTER (len=data_name_length), &
865  & DIMENSION(v3fit_max_parameters) :: rp_type = ''
866 
867  INTEGER, &
868  & DIMENSION(v3fit_max_parameters) :: rp_index = 0
869 
870  INTEGER, &
871  & DIMENSION(v3fit_max_parameters) :: rp_index2 = 0
872 
873  REAL (rprec), &
874  & DIMENSION(v3fit_max_parameters) :: rp_vrnc = 0.0
875 
880  CHARACTER (len=data_name_length), &
881  & DIMENSION(v3fit_max_parameters,2) :: rp_range_type = 'infinity'
882 
884  REAL (rprec), &
885  & DIMENSION(v3fit_max_parameters,2) :: rp_range_value = 0.0
886 
888  INTEGER, DIMENSION(v3fit_max_parameters,2,data_max_indices) :: &
889  & rp_range_index = 0
890 
891 ! Reconstruction parameters
893  INTEGER :: n_lp = 0
895  CHARACTER (len=data_name_length), &
896  & DIMENSION(v3fit_max_parameters) :: lp_type = ''
897 
898  INTEGER, &
899  & DIMENSION(v3fit_max_parameters) :: lp_index = 0
900 
901  INTEGER, &
902  & DIMENSION(v3fit_max_parameters) :: lp_index2 = 0
903 
904  CHARACTER (len=data_name_length), &
905  & DIMENSION(v3fit_max_parameters,v3fit_max_parameters) :: &
906  & lp_sets = ''
907 
908  INTEGER, &
909  & DIMENSION(v3fit_max_parameters,v3fit_max_parameters) :: &
910  & lp_sets_index = 0
911 
912  INTEGER, &
913  & DIMENSION(v3fit_max_parameters,v3fit_max_parameters) :: &
914  & lp_sets_index2 = 0
915 
916  REAL (rprec), &
917  & DIMENSION(v3fit_max_parameters,v3fit_max_parameters) :: &
918  & lp_sets_coeff = 0.0
919 
920 ! Signal data
923  INTEGER :: n_sdata_o = 0
925  INTEGER :: iw_sdo_verbose = -1
927  REAL (rprec), &
928  & DIMENSION(v3fit_max_signals) :: sdo_data_a = 0.0
929 
930  REAL (rprec), &
931  & DIMENSION(v3fit_max_signals) :: sdo_sigma_a = 0.0
932 
933  REAL (rprec), &
934  & DIMENSION(v3fit_max_signals) :: sdo_weight_a = 1.0
935 
936  LOGICAL :: sdo_spec_can_overwrite = .true.
939  LOGICAL, DIMENSION(v3fit_max_diagnostics) :: mag_a = .true.
942  LOGICAL, DIMENSION(v3fit_max_diagnostics) :: mag_3d_a = .false.
944  LOGICAL :: mag_force_coil = .false.
945 
946 ! Signal data sigma specification
948  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
949  & sdo_s_spec_imin = 0
950 
951  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
952  & sdo_s_spec_imax = 0
953 
954  REAL (rprec), DIMENSION(v3fit_max_spec_size) :: &
955  & sdo_s_spec_floor = 0.0
956 
957  REAL (rprec), DIMENSION(v3fit_max_spec_size) :: &
958  & sdo_s_spec_fraction = 0.0
959 
960 ! Signal data weight specification
962  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
963  & sdo_w_spec_imin = 0
964 
965  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
966  & sdo_w_spec_imax = 0
967 
968  REAL (rprec), DIMENSION(v3fit_max_spec_size) :: &
969  & sdo_w_spec_weight = 0.0
970 
971 ! Magnetic specification
973  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
974  & mag_spec_imin = 0
975 
976  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
977  & mag_spec_imax = 0
978 
979  LOGICAL, DIMENSION(v3fit_max_spec_size) :: &
980  & mag_spec_use_induced = .true.
981 
982 ! Magnetic integration parameters
984  REAL (rprec) :: pol_rad_ratio = 1.0
985 
986 ! Signal factor parameter specification.
988  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
989  & sfactor_spec_imin = 0
990 
991  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
992  & sfactor_spec_imax = 0
993 
994  REAL (rprec), DIMENSION(v3fit_max_spec_size) :: &
995  & sfactor_spec_fac = 0.0
996 
997 ! Signal factor parameter specification.
999  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
1000  & soffset_spec_imin = 0
1001 
1002  INTEGER, DIMENSION(v3fit_max_spec_size) :: &
1003  & soffset_spec_imax = 0
1004 
1005  REAL (rprec), DIMENSION(v3fit_max_spec_size) :: &
1006  & soffset_spec_fac = 0.0
1007 
1008 ! External current signal specification
1012  REAL (rprec) :: extcurz_s0 = -1.0
1014  REAL (rprec) :: extcurz_u0 = 0.0
1015 
1016 ! Geometric information
1018  REAL (rprec) :: r_major_radius
1020  REAL (rprec) :: a_minor_radius
1021 
1022 ! Limiter iso function specification.
1024  INTEGER :: n_lif = 0
1026  INTEGER, DIMENSION(v3fit_max_limiters) :: n_phi_lif = 0
1028  REAL (rprec), DIMENSION(v3fit_max_limiters,0:4,0:4) :: &
1029  & lif_arz = 0.0
1030 
1031  REAL (rprec), DIMENSION(v3fit_max_limiters) :: lif_rc = 0.0
1033  REAL (rprec), DIMENSION(v3fit_max_limiters) :: lif_zc = 0.0
1035  REAL (rprec), DIMENSION(v3fit_max_limiters) :: &
1036  & lif_sigma = 0.001_dp
1037 
1038  REAL (rprec), DIMENSION(v3fit_max_limiters,v3fit_max_lif_size) &
1039  & :: lif_phi_degree = 0.0
1040 
1042  LOGICAL, DIMENSION(v3fit_max_limiters) :: &
1043  & lif_on_edge = .false.
1044 
1045 ! Prior signal specification.
1047  INTEGER :: n_prior = 0
1049  CHARACTER (len=data_name_length), DIMENSION(v3fit_max_priors) &
1050  & :: prior_name = ''
1051 
1052  CHARACTER (len=data_name_length), DIMENSION(v3fit_max_priors) &
1053  & :: prior_param_name = ''
1054 
1055  INTEGER, DIMENSION(v3fit_max_priors,2) :: prior_indices = 0
1057  CHARACTER (len=data_short_name_length), &
1058  & DIMENSION(v3fit_max_priors) :: prior_units = ''
1059 
1060 ! Combinations of other signals specification.
1062  INTEGER :: n_coosig = 0
1064  INTEGER, DIMENSION(v3fit_max_combinations) :: n_sig_coosig = 0
1067  INTEGER, DIMENSION(v3fit_max_combinations,v3fit_max_cos_size) :: &
1068  & coosig_indices = 0
1069 
1071  REAL (rprec), &
1072  & DIMENSION(v3fit_max_combinations,v3fit_max_cos_size) :: &
1073  & coosig_coeff = 0.0
1074 
1075  CHARACTER(len=combination_type_length), &
1076  & DIMENSION(v3fit_max_combinations) :: coosig_type = 'sum'
1077 
1078  CHARACTER (len=data_name_length), &
1079  & DIMENSION(v3fit_max_combinations) :: coosig_name = ''
1080 
1081  CHARACTER (len=data_short_name_length), &
1082  & DIMENSION(v3fit_max_combinations) :: coosig_units = ''
1083 
1084  INTEGER, DIMENSION(v3fit_max_combinations) :: coosig_wgts_id = -1
1085 
1086 ! Gaussian Process Signals specification.
1088  INTEGER :: n_gp = 0
1090  INTEGER, DIMENSION(max_gaussprocess) :: n_gp_signal = 0
1093  INTEGER, DIMENSION(max_gaussprocess,v3fit_max_signals) :: &
1094  & gp_signal_indices = 0
1095 
1096  CHARACTER(len=data_short_name_length), &
1097  & DIMENSION(max_gaussprocess) :: gp_model_type = 'none'
1098 
1099  INTEGER, DIMENSION(max_gaussprocess) :: gp_model_index = 0
1101  REAL(rprec), DIMENSION(max_gaussprocess, v3fit_max_parameters) :: &
1102  & gp_param_vrnc = 0.001
1103 
1105  REAL(rprec), DIMENSION(max_gaussprocess) :: gp_tolerance = 1.0e-4
1110  REAL(rprec), DIMENSION(max_gaussprocess) :: gp_cholesky_fact = 0.0
1111 
1112 ! Integration parameters.
1117  CHARACTER (len=data_short_name_length) :: int_method = 'add'
1120  INTEGER :: int_num_points = 40
1122  REAL (rprec) :: int_size = 0.0025
1123 
1124 ! Initial Plasma Offsets
1126  REAL (rprec) :: phi_offset = 0
1128  REAL (rprec) :: z_offset = 0
1129 
1130 ! Reconstruction step control specification.
1132  INTEGER :: nrstep = 0
1134  REAL (rprec) :: dg2_stop = 0.0
1136  REAL (rprec) :: cut_svd = 0.0
1138  REAL (rprec) :: cut_eff = 0.0
1140  REAL (rprec) :: cut_marg_eff = 0.0
1142  REAL (rprec) :: cut_delta_a = 0.0
1144  REAL (rprec) :: cut_dg2 = 0.0
1146  REAL (rprec) :: astep_max = 0.0
1153  CHARACTER (len=v3fit_step_name_length) :: step_type = 'sl'
1155  REAL (rprec) :: cut_inv_svd = 1.0e-10
1157  REAL (rprec) :: cut_comp_svd = 0.0
1159  LOGICAL :: use_central_diff = .false.
1160 
1163  LOGICAL :: l_zero_xcdot = .true.
1164 
1165 ! Declare Namelist
1166  NAMELIST/v3fit_main_nli/ &
1167  & main_nli_filename, &
1168 ! Equilibrium input files
1171 ! Signal input files
1175 ! Array allocation sizes
1176  & na_s_desc, &
1177 ! Task specification and work variables
1178  & my_task, &
1179 ! Model profile specification
1180 ! Electron Denisty
1182 ! Soft x-ray emissvity
1185  & pp_sxrem_af_a, &
1186 ! Electron temperature
1188 ! Ion temperature
1190 ! Effective charge
1192 ! Soft x-ray ratio
1194 ! Model Specification Variables
1199 ! Reconstruction constraints
1200  & n_rc, rc_type, rc_index, rc_value, &
1201 ! Derived parameters
1202  & n_dp, dp_type, dp_index, &
1203 ! Reconstruction parameters
1206 ! Locking parameters
1209 ! Signal Data specification
1213 ! Magnetic integration parameters
1214  & pol_rad_ratio, &
1215 ! Signal factor parameters
1217 ! Signal offset parameters
1219 ! External current signal specification
1222  & extcurz_s0, extcurz_u0, &
1223 ! Signal data sigma specification
1225  & sdo_s_spec_fraction, &
1226 ! Signal data weight specification
1228 ! Magnetic signal specification
1230 ! Geometric information
1232 ! Limiter iso function specification.
1235 ! Prior signal specification.
1237  & prior_units, &
1238 ! Combinations of other signals specification.
1241 ! Gaussian Process Signals specification.
1244 ! Integration parameters.
1246 ! Initial PLasma Offsets.
1247  & phi_offset, z_offset, &
1248 ! Reconstruction step control specification.
1251  & use_central_diff, &
1253  & l_zero_xcdot
1254 
1255  CONTAINS
1256 
1257 !*******************************************************************************
1258 ! UTILITY SUBROUTINES
1259 !*******************************************************************************
1260 !-------------------------------------------------------------------------------
1269 !-------------------------------------------------------------------------------
1270  SUBROUTINE v3fit_input_read_namelist(namelist_file)
1271  USE safe_open_mod
1272  USE v3_utilities, only: err_fatal
1273 
1274  IMPLICIT NONE
1275 
1276 ! Declare Arguments
1277  CHARACTER (len=*), INTENT(in) :: namelist_file
1278 
1279 ! local variables
1280  INTEGER :: iou_mnli
1281  INTEGER :: status
1282  INTEGER :: i
1283  INTEGER :: j
1284  INTEGER :: imin
1285  INTEGER :: imax
1286  REAL (rprec) :: start_time
1287 
1288 ! Start of executable code
1289  start_time = profiler_get_start_time()
1290 
1291 ! Initalize a default value of the I\O unit. V3FIT increments from there.
1292  iou_mnli = 0
1293  CALL safe_open(iou_mnli, status, trim(namelist_file), &
1294  & 'old', 'formatted')
1295  CALL assert_eq(0, status, 'v3fit_input_read_namelist' // &
1296  & ': Safe_open of ' // trim(namelist_file) // ' failed')
1297 
1298 ! Read the namelist input file.
1299  READ (iou_mnli, nml=v3fit_main_nli)
1300  CLOSE (iou_mnli, iostat=status)
1301  CALL assert_eq(0, status, 'v3fit_input_read_namelist' // &
1302  & ': Error closing ' // trim(namelist_file) // ' failed')
1303 
1304 ! Toggle use coil signals for the magnetics from the specification
1305  DO j = 1, SIZE(mag_spec_imin)
1306  IF (mag_spec_imin(j) .le. 0) EXIT
1307  imin = max(min(mag_spec_imin(j), v3fit_max_diagnostics), 1)
1308  imax = min(max(mag_spec_imax(j), imin), v3fit_max_diagnostics)
1309  mag_a(imin:imax) = mag_spec_use_induced(j)
1310  END DO
1311 
1312 ! Set weights from weight specification.
1313  DO j = 1, SIZE(sdo_w_spec_imin)
1314  IF (sdo_w_spec_imin(j) .le. 0) EXIT
1315  imin = max(min(sdo_w_spec_imin(j), v3fit_max_signals), 1)
1316  imax = min(max(sdo_w_spec_imax(j), imin), v3fit_max_signals)
1317  sdo_weight_a(imin:imax) = sdo_w_spec_weight(j)
1318  END DO
1319 
1320 ! Set sigmas from the sigma specification.
1321  DO j = 1,SIZE(sdo_s_spec_imin)
1322  IF (sdo_s_spec_imin(j) .le. 0) EXIT
1323  imin = max(min(sdo_s_spec_imin(j), v3fit_max_signals), 1)
1324  imax = min(max(sdo_s_spec_imax(j), imin), v3fit_max_signals)
1325  DO i = imin, imax
1326  IF ((sdo_sigma_a(i) .eq. 0) .or. &
1327  & sdo_spec_can_overwrite) THEN
1328  IF (sdo_s_spec_floor(j) .ge. 0) THEN
1329  sdo_sigma_a(i) = max(sdo_s_spec_floor(j), &
1330  & abs(sdo_s_spec_fraction(j)*sdo_data_a(i)))
1331  ELSE
1332  sdo_sigma_a(i) = sqrt(sdo_s_spec_floor(j)**2.0 + &
1333  & (sdo_s_spec_fraction(j)*sdo_data_a(i))**2.0)
1334  END IF
1335  END IF
1336  END DO
1337  END DO
1338 
1339  IF (main_nli_filename .eq. '') THEN
1340  main_nli_filename = namelist_file
1341  END IF
1342 
1343  IF ((r_major_radius .gt. 0.0) .and. &
1344  & (a_minor_radius .gt. 0.0)) THEN
1345  IF (n_lif + 1 .le. v3fit_max_limiters) THEN
1346  n_lif = n_lif + 1 ! Add this as a new limiter.
1347  lif_arz(n_lif,:,:) = 0.0
1348  lif_arz(n_lif,0,0) = -a_minor_radius**2.0
1349  lif_arz(n_lif,2,0) = 1.0
1350  lif_arz(n_lif,0,2) = 1.0
1352  lif_zc(n_lif) = 0.0
1353  lif_sigma(n_lif) = 0.001_rprec
1355  DO i = 1, v3fit_max_lif_size
1356  lif_phi_degree(n_lif,i) = (i - 1)*360.0 &
1357  & / v3fit_max_lif_size
1358  END DO
1359  lif_on_edge(n_lif) = .true.
1360  ELSE
1361  CALL err_fatal('Adding limiter by specifying ' // &
1362  & 'major/minor radii causes n_lif to ' // &
1363  & 'exceed v3fit_max_limiters')
1364  END IF
1365  END IF
1366 
1367 ! Search for the last index greater than 0 to determine the number of signals
1368 ! in a combination.
1370  DO i = 1, n_coosig
1371  DO j = 1, v3fit_max_cos_size
1372  IF (coosig_indices(i,j) .eq. 0) THEN
1373  n_sig_coosig(i) = j - 1
1374  EXIT ! Exit out of the j loop.
1375  END IF
1376  END DO
1377  END DO
1378 
1379 
1380 !-------------------------------------------------------------------------------
1381 ! All the coding between these boxes can be removed once the non _a sxrem
1382 ! values are removed. ***
1383 !-------------------------------------------------------------------------------
1384 ! Check the non _a sxrem profile variables. If pp_sxrem_ptype does not equal
1385 ! 'none' then over write the the first elements of the _a versions.
1386  SELECT CASE (trim(model_sxrem_type))
1387 
1388  CASE ('none') ! Do nothing
1389 
1390  CASE DEFAULT
1391  WRITE (*,*) ' *** Overwiting the sxrem profile first ' // &
1392  & 'element.'
1393  WRITE (*,*) ' Non array soft xray profiles have ' // &
1394  & 'been deprecated'
1397  pp_sxrem_b_a(1,:) = pp_sxrem_b
1398  pp_sxrem_as_a(1,:) = pp_sxrem_as
1399  pp_sxrem_af_a(1,:) = pp_sxrem_af
1400 
1401 ! We'll assume that any reconstuction parameters that refer to the non _a also
1402 ! are the first element.
1403  DO i = 1, n_rp
1404  SELECT CASE(trim(rp_type(i)))
1405 
1406  CASE ('pp_sxrem_b')
1407  WRITE (*,1000) 'pp_sxrem_b', 'pp_sxrem_b_a'
1408  rp_type(i) = 'pp_sxrem_b_a'
1409  rp_index2(i) = rp_index(i)
1410  rp_index(i) = 1
1411 
1412  CASE ('pp_sxrem_as')
1413  WRITE (*,1000) 'pp_sxrem_as', 'pp_sxrem_as_a'
1414  rp_type(i) = 'pp_sxrem_as_a'
1415  rp_index2(i) = rp_index(i)
1416  rp_index(i) = 1
1417 
1418  CASE ('pp_sxrem_af')
1419  WRITE (*,1000) 'pp_sxrem_af', 'pp_sxrem_af_a'
1420  rp_type(i) = 'pp_sxrem_af_a'
1421  rp_index2(i) = rp_index(i)
1422  rp_index(i) = 1
1423 
1424  END SELECT
1425 
1426 ! Need to update ranges as well starting with the lower range.
1427  SELECT CASE(trim(rp_range_type(i,1)))
1428 
1429  CASE ('pp_sxrem_b')
1430  WRITE (*,1001) 'pp_sxrem_b', 'pp_sxrem_b_a'
1431  rp_range_type(i,1) = 'pp_sxrem_b_a'
1432  rp_range_index(i,1,2) = rp_range_index(i,1,1)
1433  rp_range_index(i,1,1) = 1
1434 
1435  CASE ('pp_sxrem_as')
1436  WRITE (*,1001) 'pp_sxrem_as', 'pp_sxrem_as_a'
1437  rp_range_type(i,1) = 'pp_sxrem_as_a'
1438  rp_range_index(i,1,2) = rp_range_index(i,1,1)
1439  rp_range_index(i,1,1) = 1
1440 
1441  CASE ('pp_sxrem_af')
1442  WRITE (*,1001) 'pp_sxrem_af', 'pp_sxrem_af_a'
1443  rp_range_type(i,1) = 'pp_sxrem_af_a'
1444  rp_range_index(i,1,2) = rp_range_index(i,1,1)
1445  rp_range_index(i,1,1) = 1
1446 
1447  END SELECT
1448 
1449 ! Update the lower ranges.
1450  SELECT CASE(trim(rp_range_type(i,2)))
1451 
1452  CASE ('pp_sxrem_b')
1453  WRITE (*,1002) 'pp_sxrem_b', 'pp_sxrem_b_a'
1454  rp_range_type(i,2) = 'pp_sxrem_b_a'
1455  rp_range_index(i,2,2) = rp_range_index(i,2,1)
1456  rp_range_index(i,2,1) = 1
1457 
1458  CASE ('pp_sxrem_as')
1459  WRITE (*,1002) 'pp_sxrem_as', 'pp_sxrem_as_a'
1460  rp_range_type(i,2) = 'pp_sxrem_as_a'
1461  rp_range_index(i,2,2) = rp_range_index(i,2,1)
1462  rp_range_index(i,2,1) = 1
1463 
1464  CASE ('pp_sxrem_af')
1465  WRITE (*,1002) 'pp_sxrem_af', 'pp_sxrem_af_a'
1466  rp_range_type(i,2) = 'pp_sxrem_af_a'
1467  rp_range_index(i,2,2) = rp_range_index(i,2,1)
1468  rp_range_index(i,2,1) = 1
1469 
1470  END SELECT
1471  END DO
1472 
1473 ! Update priors to use _a arrays.
1474  DO i = 1, n_prior
1475  SELECT CASE(trim(prior_name(i)))
1476  CASE ('pp_sxrem_b')
1477  WRITE (*,1003) 'pp_sxrem_b', 'pp_sxrem_b_a'
1478  prior_name(i) = 'pp_sxrem_b_a'
1479  prior_indices(i,2) = prior_indices(i,1)
1480 
1481  CASE ('pp_sxrem_as')
1482  WRITE (*,1003) 'pp_sxrem_as', 'pp_sxrem_as_a'
1483  prior_name(i) = 'pp_sxrem_as_a'
1484  prior_indices(i,2) = prior_indices(i,1)
1485 
1486  CASE ('pp_sxrem_af')
1487  WRITE (*,1003) 'pp_sxrem_af', 'pp_sxrem_af_a'
1488  prior_name(i) = 'pp_sxrem_af_a'
1489  prior_indices(i,2) = prior_indices(i,1)
1490  END SELECT
1491  END DO
1492  END SELECT
1493 
1494 1000 FORMAT('Changing reconstruction parameter ',a,' to ', a)
1495 1001 FORMAT('Changing lower parameter constraint ',a,' to ', a)
1496 1002 FORMAT('Changing upper parameter constraint ',a,' to ', a)
1497 1003 FORMAT('Changing prior signal ',a,' to ', a)
1498 !-------------------------------------------------------------------------------
1499 ! All the coding between these boxes can be removed once the non _a sxrem
1500 ! values are removed. ***
1501 !-------------------------------------------------------------------------------
1502 
1503  WRITE (*,*) ' *** V3FIT namelist input read from ' // &
1504  & trim(namelist_file)
1505 
1506  CALL profiler_set_stop_time('v3fit_input_read_namelist', &
1507  & start_time)
1508 
1509  END SUBROUTINE
1510 
1511 !-------------------------------------------------------------------------------
1519 !-------------------------------------------------------------------------------
1520  FUNCTION v3fit_input_find_scale_index(index)
1522  IMPLICIT NONE
1523 
1524 ! Declare Arguments
1525  INTEGER :: v3fit_input_find_scale_index
1526  INTEGER, INTENT(in) :: index
1527 
1528 ! local variables
1529  INTEGER :: i
1530  REAL (rprec) :: start_time
1531 
1532 ! Start of executable code
1533  start_time = profiler_get_start_time()
1534 
1536  DO i = 1, v3fit_max_spec_size
1537  IF (sfactor_spec_fac(i) .eq. 0.0) THEN
1538  EXIT
1539  END IF
1540 
1541  IF (sfactor_spec_imin(i) .le. index .and. &
1542  & sfactor_spec_imax(i) .ge. index) THEN
1544  EXIT
1545  END IF
1546  END DO
1547 
1548  CALL profiler_set_stop_time('v3fit_input_find_scale_index', &
1549  & start_time)
1550 
1551  END FUNCTION
1552 
1553 !-------------------------------------------------------------------------------
1561 !-------------------------------------------------------------------------------
1562  FUNCTION v3fit_input_find_offset_index(index)
1564  IMPLICIT NONE
1565 
1566 ! Declare Arguments
1568  INTEGER, INTENT(in) :: index
1569 
1570 ! local variables
1571  INTEGER :: i
1572  REAL (rprec) :: start_time
1573 
1574 ! Start of executable code
1575  start_time = profiler_get_start_time()
1576 
1578  DO i = 1, v3fit_max_spec_size
1579  IF (soffset_spec_imin(i) .le. index .and. &
1580  & soffset_spec_imax(i) .ge. index) THEN
1582  EXIT
1583  END IF
1584  END DO
1585 
1586  CALL profiler_set_stop_time('v3fit_input_find_offset_index', &
1587  & start_time)
1588 
1589  END FUNCTION
1590 
1591 !-------------------------------------------------------------------------------
1597 !-------------------------------------------------------------------------------
1598  SUBROUTINE v3fit_input_write_namelist(namelist_file)
1599  USE safe_open_mod
1600 
1601  IMPLICIT NONE
1602 
1603 ! Declare Arguments
1604  CHARACTER (len=*), INTENT(in) :: namelist_file
1605 
1606 ! local variables
1607  INTEGER :: iou_mnli
1608  INTEGER :: status
1609  REAL (rprec) :: start_time
1610 
1611 ! Start of executable code
1612  start_time = profiler_get_start_time()
1613 
1614 ! FIXME: Update namelist variables from the context.
1615 
1616 ! Initalize a default value of the I\O unit. SIESTA increments from there.
1617  iou_mnli = 0
1618  CALL safe_open(iou_mnli, status, trim(namelist_file), &
1619  & 'replace', 'formatted', delim_in='quote')
1620  CALL assert_eq(0, status, 'v3fit_input_write_namelist' // &
1621  & ': Safe_open of ' // trim(namelist_file) // ' failed')
1622 
1623 ! Write the namelist input file.
1624  WRITE (iou_mnli, nml=siesta_info)
1625  CLOSE (iou_mnli, iostat=status)
1626  CALL assert_eq(0, status, 'v3fit_input_write_namelist' // &
1627  & ': Error closing ' // trim(namelist_file) // ' failed')
1628 
1629  CALL profiler_set_stop_time('v3fit_input_write_namelist', &
1630  & start_time)
1631 
1632  END SUBROUTINE
1633 
1634  END MODULE
v3fit_input::sdo_w_spec_weight
real(rprec), dimension(v3fit_max_spec_size) sdo_w_spec_weight
Weight specification weight.
Definition: v3fit_input.f:968
v3fit_input::gp_model_type
character(len=data_short_name_length), dimension(max_gaussprocess) gp_model_type
Gaussian process model type.
Definition: v3fit_input.f:1096
v3fit_input::dp_index
integer, dimension(v3fit_max_parameters, 2) dp_index
Indices of derived parameters.
Definition: v3fit_input.f:857
v3fit_input::pp_ti_af
real(rprec), dimension(iub_asf) pp_ti_af
Array of af_coefficients ion temperature splines.
Definition: v3fit_input.f:765
v3fit_input::siesta_restart_filename
character(len=path_length) siesta_restart_filename
File name for a siesta restart file.
Definition: v3fit_input.f:637
v3fit_input::main_nli_filename
character(len=path_length) main_nli_filename
File name for main namelist input. Namelist v3fit_main_nli definition.
Definition: v3fit_input.f:625
v3fit_input::lif_on_edge
logical, dimension(v3fit_max_limiters) lif_on_edge
True specifies that the edge hits the limiter. False specifies that the edge is inside the limiter.
Definition: v3fit_input.f:1042
v3fit_input::pp_ti_as
real(rprec), dimension(iub_asf) pp_ti_as
Array of as_coefficients ion temperature splines.
Definition: v3fit_input.f:762
v3fit_input::pp_ne_as
real(rprec), dimension(iub_asf) pp_ne_as
Array of as_coefficients electron density splines.
Definition: v3fit_input.f:687
combination
Defines the base class of the type combination_class.
Definition: combination.f:13
v3fit_input::pp_ze_as
real(rprec), dimension(iub_asf) pp_ze_as
Array of as_coefficients effective charge splines.
Definition: v3fit_input.f:778
v3fit_input::sdo_spec_can_overwrite
logical sdo_spec_can_overwrite
Allow the sigma spec to overwrite the sigma array.
Definition: v3fit_input.f:936
v3fit_input::cut_delta_a
real(rprec) cut_delta_a
Cutoff value for expected step size.
Definition: v3fit_input.f:1142
v3fit_input::rp_index2
integer, dimension(v3fit_max_parameters) rp_index2
Jth index of reconstruction parameters.
Definition: v3fit_input.f:870
v3fit_input::rp_type
character(len=data_name_length), dimension(v3fit_max_parameters) rp_type
Names of reconstruction parameters.
Definition: v3fit_input.f:864
v3fit_input::pp_ne_af
real(rprec), dimension(iub_asf) pp_ne_af
Array of af_coefficients electron density splines.
Definition: v3fit_input.f:690
v3fit_input::rp_index
integer, dimension(v3fit_max_parameters) rp_index
Ith index of reconstruction parameters.
Definition: v3fit_input.f:867
v3fit_input::n_dp
integer n_dp
Number of derived parameters.
Definition: v3fit_input.f:852
v3fit_input::coosig_coeff
real(rprec), dimension(v3fit_max_combinations, v3fit_max_cos_size) coosig_coeff
Coefficients of the signals to combine. Number if indices needs to match n_sig_coosig.
Definition: v3fit_input.f:1071
v3fit_input::v3fit_input_read_namelist
subroutine v3fit_input_read_namelist(namelist_file)
Reads the namelist input file.
Definition: v3fit_input.f:1271
v3fit_input::prior_indices
integer, dimension(v3fit_max_priors, 2) prior_indices
Prior parameter indicies.
Definition: v3fit_input.f:1055
v3fit_input::model_sxrem_type
character(len=data_name_length) model_sxrem_type
Definition: v3fit_input.f:801
v3fit_input::v3fit_max_limiters
integer, parameter v3fit_max_limiters
Maximum number of geometric signals.
Definition: v3fit_input.f:584
v3fit_input::rc_value
real(rprec), dimension(v3fit_max_parameters) rc_value
Not implemented.
Definition: v3fit_input.f:847
v3fit_input::ze_min
real(rprec) ze_min
Minimum effective charge.
Definition: v3fit_input.f:825
v3fit_input::dg2_stop
real(rprec) dg2_stop
Stopping criterion on change in g^2.
Definition: v3fit_input.f:1134
v3fit_input::e_pressure_fraction
real(rprec) e_pressure_fraction
Specifies the fraction of the pressure constributed by the electrons.
Definition: v3fit_input.f:829
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
v3fit_input::pp_te_ptype
character(len=p_type_len) pp_te_ptype
Model electron temperature profile, parameterized profile type.
Definition: v3fit_input.f:740
v3fit_input::n_sig_coosig
integer, dimension(v3fit_max_combinations) n_sig_coosig
Number of signals in a combination signal.
Definition: v3fit_input.f:1064
v3fit_input::cut_svd
real(rprec) cut_svd
Cutoff value for relative Singular Values.
Definition: v3fit_input.f:1136
v3fit_input::v3fit_input_find_scale_index
integer function v3fit_input_find_scale_index(index)
Finds the index of the scaling spec.
Definition: v3fit_input.f:1521
v3fit_input::pp_ti_b
real(rprec), dimension(ilb_b:iub_b) pp_ti_b
Array of b_coefficients for the ion temperature profile.
Definition: v3fit_input.f:759
v3fit_input::sxrch_dot_filename
character(len=path_length) sxrch_dot_filename
File holding sxr chord information.
Definition: v3fit_input.f:643
v3fit_input::gp_signal_indices
integer, dimension(max_gaussprocess, v3fit_max_signals) gp_signal_indices
Indices of the number signals to include in the GP. Number of indices needs to match n_sig_gpsig.
Definition: v3fit_input.f:1093
v3fit_input::pp_sxrem_ptype
character(len=p_type_len) pp_sxrem_ptype
Definition: v3fit_input.f:698
v3fit_input::pp_sxrem_af
real(rprec), dimension(iub_asf) pp_sxrem_af
Definition: v3fit_input.f:710
v3fit_input::pol_rad_ratio
real(rprec) pol_rad_ratio
Ratio of the number of poloidal grid points to radial grid points.
Definition: v3fit_input.f:984
v3fit_input::lif_phi_degree
real(rprec), dimension(v3fit_max_limiters, v3fit_max_lif_size) lif_phi_degree
Array of phi values. Number of phi values need to be match n_phi_lif.
Definition: v3fit_input.f:1038
v3fit_input::pp_ze_b
real(rprec), dimension(ilb_b:iub_b) pp_ze_b
Array of b_coefficients for the effective charge profile.
Definition: v3fit_input.f:775
v3fit_input
This file contains all the variables and maximum sizes of the inputs for a v3fit namelist input file....
Definition: v3fit_input.f:570
v3fit_input::na_s_desc
integer na_s_desc
Maximum number of signals to create.
Definition: v3fit_input.f:664
v3_utilities::assert_eq
Definition: v3_utilities.f:62
v3fit_input::soffset_spec_fac
real(rprec), dimension(v3fit_max_spec_size) soffset_spec_fac
Signal scale factor.
Definition: v3fit_input.f:1005
v3fit_input::lp_index
integer, dimension(v3fit_max_parameters) lp_index
Ith index of locking parameters.
Definition: v3fit_input.f:898
v3fit_input::n_sdata_o
integer n_sdata_o
Definition: v3fit_input.f:923
v3fit_input::v3fit_max_lif_size
integer, parameter v3fit_max_lif_size
Maximum number of phi positions for limiters.
Definition: v3fit_input.f:610
v3fit_input::coosig_type
character(len=combination_type_length), dimension(v3fit_max_combinations) coosig_type
Combination type.
Definition: v3fit_input.f:1075
v3fit_input::gp_tolerance
real(rprec), dimension(max_gaussprocess) gp_tolerance
Convergence criteria for the gradient ascent to maximize the log of the evidence.
Definition: v3fit_input.f:1105
v3fit_input::mag_a
logical, dimension(v3fit_max_diagnostics) mag_a
Magnetic signal flags. Controls if the induced signal is included in the total signal.
Definition: v3fit_input.f:939
v3fit_input::v3fit_max_parameters
integer, parameter v3fit_max_parameters
Maximum number of reconstruction parameters.
Definition: v3fit_input.f:597
v3fit_input::a_minor_radius
real(rprec) a_minor_radius
Geometric limiter minor radius.
Definition: v3fit_input.f:1020
v3fit_input::mag_3d_a
logical, dimension(v3fit_max_diagnostics) mag_3d_a
Magnetic signal flags. Controls if the axisymmetric part of the signal is removed from the model sign...
Definition: v3fit_input.f:942
v3fit_input::ne_min
real(rprec) ne_min
Minimum electron density.
Definition: v3fit_input.f:819
v3fit_input::model_sxrem_type_a
character(len=data_name_length), dimension(max_sxrem_profiles) model_sxrem_type_a
Specify how soft x-ray emissivity is computed by the model.
Definition: v3fit_input.f:804
v3fit_input::sdo_s_spec_imax
integer, dimension(v3fit_max_spec_size) sdo_s_spec_imax
Sigma specification upper index.
Definition: v3fit_input.f:951
v3fit_input::pp_te_af
real(rprec), dimension(iub_asf) pp_te_af
Array of af_coefficients electron temperature splines.
Definition: v3fit_input.f:749
v3fit_input::rp_range_type
character(len=data_name_length), dimension(v3fit_max_parameters, 2) rp_range_type
Parameter range types. The first index is the lower range and second index the upper range.
Definition: v3fit_input.f:880
v3fit_input::pp_sxrem_as
real(rprec), dimension(iub_asf) pp_sxrem_as
Definition: v3fit_input.f:706
v3fit_input::n_coosig
integer n_coosig
Number of combination signals.
Definition: v3fit_input.f:1062
v3fit_input::dp_type
character(len=data_name_length), dimension(v3fit_max_parameters) dp_type
Names of derived parameters.
Definition: v3fit_input.f:854
v3fit_input::rc_type
character(len=data_name_length), dimension(v3fit_max_parameters) rc_type
Not implemented.
Definition: v3fit_input.f:841
v3fit_input::te_min
real(rprec) te_min
Minimum electron temperature.
Definition: v3fit_input.f:821
v3fit_input::sdo_sigma_a
real(rprec), dimension(v3fit_max_signals) sdo_sigma_a
Observed sigmas.
Definition: v3fit_input.f:930
v3fit_input::ipch_dot_filename
character(len=path_length) ipch_dot_filename
File holding interferometry-polarimetry information. Inteferometry/Polarimetry Diagnostic Dot File.
Definition: v3fit_input.f:646
v3fit_input::mag_force_coil
logical mag_force_coil
Forces the magnetic signal to compute the induced signal.
Definition: v3fit_input.f:944
v3fit_input::ece_resonance_range
real(rprec) ece_resonance_range
ECE resonance search range.
Definition: v3fit_input.f:833
v3fit_input::int_size
real(rprec) int_size
Real control of numerical quadrature. Set dx for addivative integration.
Definition: v3fit_input.f:1122
v3fit_input::my_task
character(len=data_name_length) my_task
The v3fit task. Possible values are.
Definition: v3fit_input.f:672
v3fit_input::sdo_weight_a
real(rprec), dimension(v3fit_max_signals) sdo_weight_a
Observed weights.
Definition: v3fit_input.f:933
v3fit_input::model_eq_type
character(len=data_name_length) model_eq_type
Specify wich equilibrium to use.
Definition: v3fit_input.f:791
v3fit_input::cut_inv_svd
real(rprec) cut_inv_svd
Cutoff value for singular values in matrix inverse.
Definition: v3fit_input.f:1155
v3fit_input::soffset_spec_imax
integer, dimension(v3fit_max_spec_size) soffset_spec_imax
Signal factor specification upper index.
Definition: v3fit_input.f:1002
v3fit_input::r_major_radius
real(rprec) r_major_radius
Geometric limiter major radius.
Definition: v3fit_input.f:1018
v3fit_input::rp_range_index
integer, dimension(v3fit_max_parameters, 2, data_max_indices) rp_range_index
Parameter range indices. The first index is the lower range and second index the upper range.
Definition: v3fit_input.f:888
v3fit_input::use_central_diff
logical use_central_diff
Use central differencing to compute the jacobian.
Definition: v3fit_input.f:1159
v3fit_input::thscte_dot_filename
character(len=path_length) thscte_dot_filename
File holding Thomson Scattering information.
Definition: v3fit_input.f:648
v3fit_input::sxrem_ratio_a
real(rprec), dimension(iub_asf) sxrem_ratio_a
Array of ratio points for the sxrem ratio function.
Definition: v3fit_input.f:787
v3fit_input::lif_arz
real(rprec), dimension(v3fit_max_limiters, 0:4, 0:4) lif_arz
Array of r-z polynomial coefficients.
Definition: v3fit_input.f:1028
v3fit_input::sfactor_spec_fac
real(rprec), dimension(v3fit_max_spec_size) sfactor_spec_fac
Signal scale factor.
Definition: v3fit_input.f:994
v3fit_input::step_type
character(len=v3fit_step_name_length) step_type
Reconstruction step type. Possible values are:
Definition: v3fit_input.f:1153
v3fit_input::mdsig_list_filename
character(len=path_length) mdsig_list_filename
File name for list of MDSIG files.
Definition: v3fit_input.f:641
v3fit_input::vmec_wout_input
character(len=path_length) vmec_wout_input
File name for the VMEC wout input.
Definition: v3fit_input.f:631
v3fit_input::mag_spec_imin
integer, dimension(v3fit_max_spec_size) mag_spec_imin
Magnetic specification lower index.
Definition: v3fit_input.f:973
v3fit_input::coosig_wgts_id
integer, dimension(v3fit_max_combinations) coosig_wgts_id
Array of parameter weight ids to use in the combination signal.
Definition: v3fit_input.f:1084
v3fit_input::prior_param_name
character(len=data_name_length), dimension(v3fit_max_priors) prior_param_name
Prior parameter names.
Definition: v3fit_input.f:1052
v3fit_input::mag_spec_imax
integer, dimension(v3fit_max_spec_size) mag_spec_imax
Magnetic specification upper index.
Definition: v3fit_input.f:976
v3fit_input::model_ti_type
character(len=data_name_length) model_ti_type
Specify how electron temperature is computed by the model.
Definition: v3fit_input.f:812
v3fit_input::pp_sxrem_b
real(rprec), dimension(ilb_b:iub_b) pp_sxrem_b
Definition: v3fit_input.f:702
v3fit_input::vacuum_nli_filename
character(len=path_length) vacuum_nli_filename
File name for a vacuum namelist input.
Definition: v3fit_input.f:633
v3fit_input::mse_dot_filename
character(len=path_length) mse_dot_filename
File holding motional stark effect information.
Definition: v3fit_input.f:650
data_parameters::max_gaussprocess
integer, parameter max_gaussprocess
Maximum number of Gaussian Process signals. Total number of auxillary profiles.
Definition: data_parameters.f:55
v3fit_input::int_method
character(len=data_short_name_length) int_method
Integation method. The evaultion the K_LL matrix can require multipe evaluation of a double path inte...
Definition: v3fit_input.f:1117
v3fit_input::pp_sxrem_ptype_a
character(len=p_type_len), dimension(max_sxrem_profiles) pp_sxrem_ptype_a
Model soft x-ray emissvity profile, parameterized profile type.
Definition: v3fit_input.f:719
v3fit_input::v3fit_max_cos_size
integer, parameter v3fit_max_cos_size
Maximum number of signals a combination signal can refer to.
Definition: v3fit_input.f:613
v3fit_input::sfactor_spec_imax
integer, dimension(v3fit_max_spec_size) sfactor_spec_imax
Signal factor specification upper index.
Definition: v3fit_input.f:991
v3fit_input::n_rp
integer n_rp
Number of reconstruction parameters.
Definition: v3fit_input.f:862
v3fit_input::v3fit_max_spec_size
integer, parameter v3fit_max_spec_size
Maximum size of the easy specification arrays.
Definition: v3fit_input.f:607
v3fit_input::nrstep
integer nrstep
Max number of reconstruction steps to perform.
Definition: v3fit_input.f:1132
v3fit_input::pp_ne_b
real(rprec), dimension(ilb_b:iub_b) pp_ne_b
Array of b_coefficients for the electron density profile.
Definition: v3fit_input.f:684
v3fit_input::cut_eff
real(rprec) cut_eff
Cutoff value for expected step efficiency.
Definition: v3fit_input.f:1138
v3fit_input::iw_sdo_verbose
integer iw_sdo_verbose
Not implemented.
Definition: v3fit_input.f:925
v3fit_input::pp_sxrem_af_a
real(rprec), dimension(max_sxrem_profiles, iub_asf) pp_sxrem_af_a
Array of af_coefficients soft x-ray emissvity profile splines.
Definition: v3fit_input.f:731
v3fit_input::n_lp
integer n_lp
Number of locking parameters.
Definition: v3fit_input.f:893
v3fit_input::lif_sigma
real(rprec), dimension(v3fit_max_limiters) lif_sigma
Array of sigma values.
Definition: v3fit_input.f:1035
v3fit_input::astep_max
real(rprec) astep_max
Maximum allowable normalized step size.
Definition: v3fit_input.f:1146
v3fit_input::rp_vrnc
real(rprec), dimension(v3fit_max_parameters) rp_vrnc
Maximum reconstruction increment.
Definition: v3fit_input.f:873
v3fit_input::sdo_w_spec_imin
integer, dimension(v3fit_max_spec_size) sdo_w_spec_imin
Weight specification lower index.
Definition: v3fit_input.f:962
v3fit_input::n_gp_signal
integer, dimension(max_gaussprocess) n_gp_signal
Number of signals in a gaussian process signal.
Definition: v3fit_input.f:1090
v3fit_input::sxrem_te_a
real(rprec), dimension(iub_asf) sxrem_te_a
Array of temperature points for the sxrem ratio function.
Definition: v3fit_input.f:785
v3fit_input::gp_param_vrnc
real(rprec), dimension(max_gaussprocess, v3fit_max_parameters) gp_param_vrnc
Variances for the hyper parameters.
Definition: v3fit_input.f:1101
v3fit_input::soffset_spec_imin
integer, dimension(v3fit_max_spec_size) soffset_spec_imin
Signal factor specification lower index.
Definition: v3fit_input.f:999
v3fit_input::n_lif
integer n_lif
Number of specified limiter iso functions.
Definition: v3fit_input.f:1024
v3fit_input::v3fit_step_name_length
integer, parameter v3fit_step_name_length
Reconstruction step name length.
Definition: v3fit_input.f:616
v3fit_input::cut_dg2
real(rprec) cut_dg2
Cutoff value for expected change in g^2.
Definition: v3fit_input.f:1144
v3fit_input::sdo_s_spec_floor
real(rprec), dimension(v3fit_max_spec_size) sdo_s_spec_floor
Sigma specification floor.
Definition: v3fit_input.f:954
v3fit_input::pp_ze_af
real(rprec), dimension(iub_asf) pp_ze_af
Array of af_coefficients effective charge splines.
Definition: v3fit_input.f:781
v3fit_input::mag_spec_use_induced
logical, dimension(v3fit_max_spec_size) mag_spec_use_induced
Magnetic specification toggle induced coil signal.
Definition: v3fit_input.f:979
v3fit_input::extcurz_s0
real(rprec) extcurz_s0
External Z current radial position.
Definition: v3fit_input.f:1012
v3fit_input::l_zero_xcdot
logical l_zero_xcdot
Zero out vmec xcdot array.
Definition: v3fit_input.f:1163
v3fit_input::gp_model_index
integer, dimension(max_gaussprocess) gp_model_index
Gaussian process model type ID for models with multiple profiles.
Definition: v3fit_input.f:1099
v3fit_input::pp_sxrem_as_a
real(rprec), dimension(max_sxrem_profiles, iub_asf) pp_sxrem_as_a
Array of as_coefficients soft x-ray emissvity profile splines.
Definition: v3fit_input.f:727
v3fit_input::pp_sxrem_b_a
real(rprec), dimension(max_sxrem_profiles, ilb_b:iub_b) pp_sxrem_b_a
Array of b_coefficients for the soft x-ray emissvity profile.
Definition: v3fit_input.f:723
v3fit_input::extcurz_u0
real(rprec) extcurz_u0
External Z current poloidal angle.
Definition: v3fit_input.f:1014
v3fit_input::lp_sets
character(len=data_name_length), dimension(v3fit_max_parameters, v3fit_max_parameters) lp_sets
Names of parameters to lock to.
Definition: v3fit_input.f:904
v3fit_input::rp_range_value
real(rprec), dimension(v3fit_max_parameters, 2) rp_range_value
Parameter range value. The first index is the lower range and second index the upper range.
Definition: v3fit_input.f:884
v3fit_input::int_num_points
integer int_num_points
Integer control of numerical quadrature. For Gauss-legendre integration This parameter sets the numbe...
Definition: v3fit_input.f:1120
v3fit_input::lif_zc
real(rprec), dimension(v3fit_max_limiters) lif_zc
Array of z offset values.
Definition: v3fit_input.f:1033
v3fit_input::n_prior
integer n_prior
Number of specified priors.
Definition: v3fit_input.f:1047
v3fit_input::sdo_s_spec_imin
integer, dimension(v3fit_max_spec_size) sdo_s_spec_imin
Sigma specification lower index.
Definition: v3fit_input.f:948
v3fit_input::sfactor_spec_imin
integer, dimension(v3fit_max_spec_size) sfactor_spec_imin
Signal factor specification lower index.
Definition: v3fit_input.f:988
v3fit_input::pp_te_b
real(rprec), dimension(ilb_b:iub_b) pp_te_b
Array of b_coefficients for the electron temperature profile.
Definition: v3fit_input.f:743
v3fit_input::model_ne_type
character(len=data_name_length) model_ne_type
Specify how electron density is computed by the model.
Definition: v3fit_input.f:797
v3fit_input::cut_marg_eff
real(rprec) cut_marg_eff
Cutoff value for expected marginal step efficiency.
Definition: v3fit_input.f:1140
v3fit_input::lp_index2
integer, dimension(v3fit_max_parameters) lp_index2
Jth index of locking parameters.
Definition: v3fit_input.f:901
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
v3fit_input::lp_sets_coeff
real(rprec), dimension(v3fit_max_parameters, v3fit_max_parameters) lp_sets_coeff
Lock parameter coefficients.
Definition: v3fit_input.f:916
v3fit_input::coosig_units
character(len=data_short_name_length), dimension(v3fit_max_combinations) coosig_units
Units of the combination.
Definition: v3fit_input.f:1081
v3fit_input::ece_dot_filename
character(len=path_length) ece_dot_filename
File holding ECE information.
Definition: v3fit_input.f:652
v3fit_input::v3fit_input_write_namelist
subroutine v3fit_input_write_namelist(namelist_file)
Write the namelist input file.
Definition: v3fit_input.f:1599
v3fit_input::cut_comp_svd
real(rprec) cut_comp_svd
Cutoff value for singular values used in the magnetic data compression.
Definition: v3fit_input.f:1157
v3fit_input::model_te_type
character(len=data_name_length) model_te_type
Specify how electron temperature is computed by the model.
Definition: v3fit_input.f:809
v3fit_input::lp_type
character(len=data_name_length), dimension(v3fit_max_parameters) lp_type
Names of locking parameters.
Definition: v3fit_input.f:895
v3fit_input::v3fit_max_combinations
integer, parameter v3fit_max_combinations
Maximum number of combination signals.
Definition: v3fit_input.f:588
v3fit_input::lif_rc
real(rprec), dimension(v3fit_max_limiters) lif_rc
Array of r offset values.
Definition: v3fit_input.f:1031
pprofile_t
Defines the base class of the type pprofile_class. This module contains all the code necessary to def...
Definition: pprofile_T.f:88
v3fit_input::coosig_name
character(len=data_name_length), dimension(v3fit_max_combinations) coosig_name
Name of the combination.
Definition: v3fit_input.f:1078
v3fit_input::pp_ze_ptype
character(len=p_type_len) pp_ze_ptype
Model effective charge profile, parameterized profile type.
Definition: v3fit_input.f:772
v3fit_input::n_rc
integer n_rc
Not implemented.
Definition: v3fit_input.f:839
v3fit_input::ne_pp_unit
real(rprec) ne_pp_unit
Normalization factor for the electron density.
Definition: v3fit_input.f:817
v3fit_input::rc_index
integer, dimension(v3fit_max_parameters) rc_index
Not implemented.
Definition: v3fit_input.f:844
v3fit_input::num_sxrem_p
integer num_sxrem_p
Number of sxrem profiles.
Definition: v3fit_input.f:714
v3fit_input::coosig_indices
integer, dimension(v3fit_max_combinations, v3fit_max_cos_size) coosig_indices
Indices of the number signals to combine. Number if indices needs to match n_sig_coosig.
Definition: v3fit_input.f:1067
v3fit_input::phi_offset
real(rprec) phi_offset
Offset of plasma relative to the diagnostics.
Definition: v3fit_input.f:1126
v3fit_input::lp_sets_index2
integer, dimension(v3fit_max_parameters, v3fit_max_parameters) lp_sets_index2
Jth index of parameters to lock to.
Definition: v3fit_input.f:912
v3fit_input::pp_te_as
real(rprec), dimension(iub_asf) pp_te_as
Array of as_coefficients electron temperature splines.
Definition: v3fit_input.f:746
v3fit_input::v3fit_input_find_offset_index
integer function v3fit_input_find_offset_index(index)
Finds the index of the offset spec.
Definition: v3fit_input.f:1563
v3fit_input::prior_units
character(len=data_short_name_length), dimension(v3fit_max_priors) prior_units
Prior Units.
Definition: v3fit_input.f:1057
v3fit_input::pp_ti_ptype
character(len=p_type_len) pp_ti_ptype
Model ion temperature profile, parameterized profile type.
Definition: v3fit_input.f:756
v3fit_input::sdo_s_spec_fraction
real(rprec), dimension(v3fit_max_spec_size) sdo_s_spec_fraction
Sigma specification fraction.
Definition: v3fit_input.f:957
v3fit_input::sxrem_min
real(rprec), dimension(max_sxrem_profiles) sxrem_min
Minimum soft x-ray emission.
Definition: v3fit_input.f:827
v3fit_input::lp_sets_index
integer, dimension(v3fit_max_parameters, v3fit_max_parameters) lp_sets_index
Ith index of parameters to lock to.
Definition: v3fit_input.f:908
v3fit_input::vmec_nli_filename
character(len=path_length) vmec_nli_filename
File name for VMEC namelist input.
Definition: v3fit_input.f:629
v3fit_input::sdo_data_a
real(rprec), dimension(v3fit_max_signals) sdo_data_a
Observed signals.
Definition: v3fit_input.f:927
v3fit_input::n_gp
integer n_gp
Number of gaussian process signals.
Definition: v3fit_input.f:1088
v3fit_input::siesta_nli_filename
character(len=path_length) siesta_nli_filename
File name for a siesta namelist input.
Definition: v3fit_input.f:635
v3fit_input::ti_min
real(rprec) ti_min
Minimum ion temperature.
Definition: v3fit_input.f:823
v3fit_input::pp_ne_ptype
character(len=p_type_len) pp_ne_ptype
Model electron density profile, parameterized profile type.
Definition: v3fit_input.f:681
v3fit_input::v3fit_max_signals
integer, parameter v3fit_max_signals
Maximum number of total signals.
Definition: v3fit_input.f:590
v3fit_input::gp_cholesky_fact
real(rprec), dimension(max_gaussprocess) gp_cholesky_fact
The Gaussian process uses a cholesky decompositions to factor a matrix. It assumes that the matrix is...
Definition: v3fit_input.f:1110
v3fit_input::n_phi_lif
integer, dimension(v3fit_max_limiters) n_phi_lif
Number of phi planes for an iso functions.
Definition: v3fit_input.f:1026
v3fit_input::v3fit_max_priors
integer, parameter v3fit_max_priors
Maximum number of prior signals.
Definition: v3fit_input.f:586
v3fit_input::emission_file
character(len=data_name_length) emission_file
Specifies the path to the file contain the soft x-ray emission function.
Definition: v3fit_input.f:831
v3fit_input::limiter_grid_file
character(len=path_length) limiter_grid_file
Limiter grid netcdf file.
Definition: v3fit_input.f:656
v3fit_input::sdo_w_spec_imax
integer, dimension(v3fit_max_spec_size) sdo_w_spec_imax
Weight specification upper index.
Definition: v3fit_input.f:965
v3fit_input::coosig_wgts
real(rprec), dimension(v3fit_max_parameters) coosig_wgts
Array of combination parameter signal weights.
Definition: v3fit_input.f:835
v3fit_input::prior_name
character(len=data_name_length), dimension(v3fit_max_priors) prior_name
Prior names.
Definition: v3fit_input.f:1049
v3fit_input::sxrem_ratio_dot_filename
character(len=path_length) sxrem_ratio_dot_filename
File holding soft x-ray ratio information.
Definition: v3fit_input.f:654
v3fit_input::model_ze_type
character(len=data_name_length) model_ze_type
Specify how effective chagre is computed by the model.
Definition: v3fit_input.f:815
v3fit_input::z_offset
real(rprec) z_offset
Vertical shift of plasma relative to the center.
Definition: v3fit_input.f:1128