!
! This file is part of SACAMOS, State of the Art CAble MOdels for Spice.
! It was developed by the University of Nottingham and the Netherlands Aerospace
! Centre (NLR) for ESA under contract number 4000112765/14/NL/HK.
!
! Copyright (C) 2016-2018 University of Nottingham
!
! SACAMOS is free software: you can redistribute it and/or modify it under the
! terms of the GNU General Public License as published by the Free Software
! Foundation, either version 3 of the License, or (at your option) any later
! version.
!
! SACAMOS is distributed in the hope that it will be useful, but
! WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
! or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
! for more details.
!
! A copy of the GNU General Public License version 3 can be found in the
! file GNU_GPL_v3 in the root or at .
!
! SACAMOS uses the EISPACK library (in /SRC/EISPACK). EISPACK is subject to
! the GNU Lesser General Public License. A copy of the GNU Lesser General Public
! License version can be found in the file GNU_LGPL in the root of EISPACK
! (/SRC/EISPACK ) or at .
!
! The University of Nottingham can be contacted at: ggiemr@nottingham.ac.uk
!
!
! File Contents:
! PROGRAM spice_cable_bundle_model_builder
!
! NAME
! spice_cable_bundle_model_builder
!
! AUTHORS
! Chris Smartt
!
! DESCRIPTION
! The spice_cable_bundle_model_builder takes a previously specified cable bundle model and
! generates a spice circuit model for a specific analysis scenario e.g
! crosstalk analysis, plane wave illumination analysis etc. for a specified cable bundle length
! The code also allows the generation of a validation test case and an analytic solution
! for this test case so that the accuracy and validity of the model can be assessed.
!
! The input to the program is the name of a spice cable bundle specification file.
! A file 'name.spice_model_spec' must exist, containing all the data required to specify
! a spice cable bundle model and validation test circuit.
!
! The .cable and .bundle files referred to in the .spice_mode_spec file are looked for in directories specified
! in the .spice_model_spec file. These may be the local directory (./) other specified paths. In this way the software can interact with a
! library of cable models (MOD).
!
! The output of the spice_cable_model_builder code are the following files:
!
! name_LTspice.lib Subcircuit file suitable for use in LTspice
! name_NGspice.lib Subcircuit file suitable for use in Ngspice
! name_Pspice.lib Subcircuit file suitable for use in Pspice
!
! name_LTspice.cir Circuit file for the validation test cirucit suitable for use in LTspice
! name_NGspice.cir Circuit file for the validation test cirucit suitable for use in Ngspice
! name_Pspice.cir Circuit file for the validation test cirucit suitable for use in Pspice
!
! name.sym Schematic symbol file for use in gschem
! name.asy Schematic symbol file for use in LTspice
!
! analytic_solution.dat Analytic solution for the validation test cirucit
! spice_solution.dat Spice solution for the validation test cirucit
!
! The .lib files are placed in a directory specified in the .spice_model_spec file. This may be the local directory (./)
! or another specified path. In this way the software can interact with a library of cable models (MOD).
!!
! The program may be run with the cable name specified in the command line i.e. 'spice_cable_bundle_model_builder name'
! or it the name is absent from the command line, the user is prompted for the name.
!
! COMMENTS
! Updated to V2
!
! HISTORY
!
! started 17/11/2015 CJS: STAGE_1 developments
! started 1/02/2016 CJS: STAGE_2 developments
! started 24/03/2016 CJS: STAGE_3 developments
! started 10/05/2016 CJS: STAGE_5 developments
! started 13/06/2016 CJS: STAGE_6 developments
! Include ground plane into incident field excitation 28/6/2016 CJS
! Use frequency_spec structure for all frequency ranges 15/12/2016 CJS
! December 2016 CJS Version 2
! 24/2/2017 CJS Allow the input name to include a path i.e. the _spec file does not need to be local.
! 28/2/2017 CJS Make the validation test circuit model optional
! 16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
! 24/11/2023 CJS Start to embed FastHenry2 frequency dependent impedance matrix
!
PROGRAM spice_cable_bundle_model_builder
USE type_specifications
USE general_module
USE constants
USE cable_module
USE cable_bundle_module
USE spice_cable_bundle_module
USE MTL_analytic_solution
USE create_spice_model
USE frequency_spec
IMPLICIT NONE
! local variables
! command line argument value and length
character(len=filename_length) :: argument1
integer :: argument1_length
character(len=filename_length) :: spice_model_name_with_path ! name of the spice model including the path
character(len=filename_length) :: spice_model_path ! path to the spice model_spec file
character(len=filename_length) :: spice_model_name ! name of the spice model
character(len=filename_length) :: filename ! filename for the .spice_model_spec file
logical :: file_exists
! Structure to hold the spice cable bundle model specification (see SPICE_CABLE_BUNDLE_MODULES/spice_cable_bundle_module.F90)
TYPE(spice_model_specification_type) :: spice_bundle_model
! Structure to hold the validation circuit specification
TYPE(spice_validation_test_type) :: spice_validation_test
! incident field k vector dotted with the ground plane normal - used to check that the incident field vector is not from below the ground plane
real(dp) :: k_dot_norm
real(dp) :: min_delay ! used to redefine the minimum transmission line delay allowed in the transmission line sub-circuit
character(len=line_length) :: line ! used to read a line from the spice_model_spec file.
character :: ch ! used to read a character from the spice_model_spec file.
integer :: ierr ! integer to return error codes from file reads
! local termporary variables
integer :: phrase_found
integer :: tot_n_conductors
integer :: system_dimension
integer :: i
! START
program_name="spice_cable_bundle_model_builder"
run_status='Started'
CALL write_program_status()
CALL read_version()
CALL write_license()
! Open the input file describing the spice cable bundle simulation (.spice_model_spec file)
! This file could be created by the associated GUI or otherwise generated
! get the first command line argument. If set then this is the cable name, if it is not set then
! it must be read
CALL get_command_argument(1 , argument1, argument1_length)
if (argument1_length.NE.0) then
spice_model_name_with_path=trim(argument1)
else
write(*,*)'Enter the name of the spice cable bundle model specification data (without .spice_model_spec extension)'
read(*,'(A)')spice_model_name_with_path
end if
CALL strip_path(spice_model_name_with_path,spice_model_path,spice_model_name)
filename=trim(spice_model_name_with_path)//spice_model_spec_file_extn
inquire(file=trim(filename),exist=file_exists)
if (.NOT.file_exists) then
run_status='ERROR: Cannot find the file:'//trim(filename)
CALL write_program_status()
STOP 1
end if
! set the version tag in the spice_bundle_model structure
spice_bundle_model%version=SPICE_CABLE_MODEL_BUILDER_version
spice_bundle_model%spice_model_name=spice_model_name
! open and read the .spice_model_spec file
OPEN(unit=spice_model_spec_file_unit,file=filename)
if (verbose) write(*,*)'Opened file:',trim(filename)
! read the bundle model name
! read the MOD directory information for the cable models, bundle models and spice bundle models
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')MOD_cable_lib_dir
CALL path_format(MOD_cable_lib_dir)
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')MOD_bundle_lib_dir
CALL path_format(MOD_bundle_lib_dir)
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')MOD_spice_bundle_lib_dir
CALL path_format(MOD_spice_bundle_lib_dir)
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')spice_symbol_dir
CALL path_format(spice_symbol_dir)
! ensure that the specified paths exist - make the MOD_bundle_lib_dir path if required
if (.NOT.path_exists(MOD_cable_lib_dir)) then
run_status='ERROR MOD_cable_lib_dir does not exist '//trim(MOD_cable_lib_dir)
CALL write_program_status()
STOP 1
end if
if (.NOT.path_exists(MOD_bundle_lib_dir)) then
run_status='ERROR: MOD_bundle_lib_dir does not exist '//trim(MOD_bundle_lib_dir)
CALL write_program_status()
STOP 1
end if
CALL check_and_make_path(MOD_spice_bundle_lib_dir)
if (.NOT.path_exists(spice_symbol_dir)) then
run_status='ERROR: spice_symbol_dir does not exist '//trim(spice_symbol_dir)
CALL write_program_status()
STOP 1
end if
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')spice_bundle_model%bundle%bundle_name
! read the bundle model
CALL read_cable_bundle(spice_bundle_model%bundle,bundle_file_unit)
tot_n_conductors=spice_bundle_model%bundle%tot_n_conductors
system_dimension=spice_bundle_model%bundle%system_dimension
! read the cable bundle length
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,*)spice_bundle_model%length
! read the Incident field excitation specification
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,*)spice_bundle_model%Eamplitude
read(spice_model_spec_file_unit,*)spice_bundle_model%ktheta,spice_bundle_model%kphi
read(spice_model_spec_file_unit,*)spice_bundle_model%etheta,spice_bundle_model%ephi
! There is the possibility that the problem could be a single domain which is shielded so check for this
! We need to implement a check as to whether the last viable domain is an external domain
! There is the possibility that the last domain is shielded so no differential mode can be excited by the incident field
if ( (spice_bundle_model%Eamplitude.NE.0d0).AND. &
(spice_bundle_model%bundle%tot_n_external_conductors.LT.2) ) then
run_status='ERROR: There must be at least two conductors in the external domain for an incident field excitation'
CALL write_program_status()
STOP 1
end if
! convert angles from degrees to radians
spice_bundle_model%Ktheta=spice_bundle_model%Ktheta*pi/180d0
spice_bundle_model%Kphi=spice_bundle_model%Kphi*pi/180d0
! only include incident field excitation terms if the amplitude is not zero
if (spice_bundle_model%Eamplitude.NE.0d0) then
spice_bundle_model%include_incident_field=.TRUE.
! work out the cartesian field components of the incident field
CALL calc_incident_field_components(spice_bundle_model%Ktheta,spice_bundle_model%Kphi, &
spice_bundle_model%Etheta,spice_bundle_model%Ephi, &
spice_bundle_model%Ex,spice_bundle_model%Ey, &
spice_bundle_model%Ez,spice_bundle_model%Hx, &
spice_bundle_model%Hy,spice_bundle_model%Hz, &
spice_bundle_model%kx,spice_bundle_model%ky,spice_bundle_model%kz)
if (spice_bundle_model%bundle%ground_plane_present) then
! Check that the incident field k vector is illuminating the cables and is not
! incident from 'below' the ground plane
k_dot_norm=spice_bundle_model%kx*spice_bundle_model%bundle%ground_plane_nx+ &
spice_bundle_model%ky*spice_bundle_model%bundle%ground_plane_ny
! k_dot_norm should be of the opposite sign to spice_bundle_model%bundle%ground_plane_cable_side
if(verbose) then
write(*,*)'ground_plane_normal:',spice_bundle_model%bundle%ground_plane_nx, &
spice_bundle_model%bundle%ground_plane_ny,0d0
write(*,*)'k.norm:',k_dot_norm
end if ! verbose
if (k_dot_norm*spice_bundle_model%bundle%ground_plane_cable_side.GT.small) then
run_status='ERROR: The incident field excitation is from below the ground plane '
CALL write_program_status()
STOP 1
end if
! check that the ground plane is aligned along the x axis. This is a restriction which could
! ultimately be removed...
if ( (abs(spice_bundle_model%bundle%ground_plane_angle-pi/2d0).GT.small).OR. &
(abs(spice_bundle_model%bundle%ground_plane_x).GT.small) .OR. &
(abs(spice_bundle_model%bundle%ground_plane_y).GT.small) ) then
write(*,*) abs(spice_bundle_model%bundle%ground_plane_angle-pi/2d0)
write(*,*) abs(spice_bundle_model%bundle%ground_plane_x)
write(*,*) abs(spice_bundle_model%bundle%ground_plane_y)
run_status='ERROR: The ground plane must be aligned along the x axis with an incident field excitation'
CALL write_program_status()
STOP 1
end if ! ground plane not on the x axis
end if ! ground plane present
else
spice_bundle_model%include_incident_field=.FALSE.
end if
! read the Transfer impedance model specification
read(spice_model_spec_file_unit,'(A)')line ! this could indicate the start of transfer impedance stuff
! look for the phrase 'transfer impedance' in the line. If it occurrs then read transfer impedance information
CALL convert_to_lower_case(line,line_length)
phrase_found=INDEX(line,'transfer impedance')
if (phrase_found.NE.0) then ! there are transfer impedance models required so read this data
read(spice_model_spec_file_unit,*)spice_bundle_model%n_transfer_impedances
ALLOCATE( spice_bundle_model%Zt_conductor(1:spice_bundle_model%n_transfer_impedances) )
ALLOCATE( spice_bundle_model%Zt_direction(1:spice_bundle_model%n_transfer_impedances) )
do i=1,spice_bundle_model%n_transfer_impedances
read(spice_model_spec_file_unit,*)spice_bundle_model%Zt_conductor(i),spice_bundle_model%Zt_direction(i)
! check that the conductor number is in the appropriate range
if ((spice_bundle_model%Zt_conductor(i).LT.1).OR.(spice_bundle_model%Zt_conductor(i).GT.tot_n_conductors)) then
write(run_status,*)'ERROR: The transfer impedance conductor number should be in the range 1 to ',tot_n_conductors
CALL write_program_status()
STOP 1
end if
if ((spice_bundle_model%Zt_direction(i).NE.1).AND.(spice_bundle_model%Zt_direction(i).NE.-1)) then
write(run_status,*)'ERROR: The transfer impedance coupling direction should be either 1 or -1'
CALL write_program_status()
STOP 1
end if
end do
else
! there are no transfer impedance models required so set the number to zero and reset the file pointer
! to the beginning of the line
spice_bundle_model%n_transfer_impedances=0
backspace(spice_model_spec_file_unit)
end if
if (verbose) write(*,*)'Number of transfer impedance models=',spice_bundle_model%n_transfer_impedances
! read the next line to see if the 'no_validation_test' is set
read(spice_model_spec_file_unit,'(A)')line
! look for the phrase 'no_validation_test' in the line. If it occurrs then turn of the validation test circuit stuff
CALL convert_to_lower_case(line,line_length)
phrase_found=INDEX(line,'no_validation_test')
if (phrase_found.NE.0) then
run_validation_test=.FALSE.
else
backspace(spice_model_spec_file_unit)
! Validation test problem information
if (verbose) then
write(*,*)'tot_n_conductors',tot_n_conductors
write(*,*)'system_dimension',system_dimension
end if
! Allocate data for termination models
ALLOCATE( spice_validation_test%Vs_end1(1:system_dimension+1) )
ALLOCATE( spice_validation_test%R_end1(1:system_dimension+1) )
ALLOCATE( spice_validation_test%Vs_end2(1:system_dimension+1) )
ALLOCATE( spice_validation_test%R_end2(1:system_dimension+1) )
! read the end 1 termination model, voltage sources then resistances
read(spice_model_spec_file_unit,*) ! comment line
do i=1,system_dimension+1
read(spice_model_spec_file_unit,*,ERR=9030)spice_validation_test%Vs_end1(i)
end do
do i=1,system_dimension+1
read(spice_model_spec_file_unit,*,ERR=9040)spice_validation_test%R_end1(i)
end do
! read the end 2 termination model, voltage sources then resistances
read(spice_model_spec_file_unit,*) ! comment line
do i=1,system_dimension+1
read(spice_model_spec_file_unit,*,ERR=9050)spice_validation_test%Vs_end2(i)
end do
do i=1,system_dimension+1
read(spice_model_spec_file_unit,*,ERR=9060)spice_validation_test%R_end2(i)
end do
! read the type of analysis
read(spice_model_spec_file_unit,*) ! comment line
read(spice_model_spec_file_unit,'(A)')ch
if ( (ch.EQ.'A').OR.(ch.EQ.'a') ) then
spice_validation_test%analysis_type=analysis_type_AC
CALL read_and_set_up_frequency_specification(spice_validation_test%analysis_freq_spec,spice_model_spec_file_unit)
else if ( (ch.EQ.'T').OR.(ch.EQ.'t') ) then
spice_validation_test%analysis_type=analysis_type_TRANS
read(spice_model_spec_file_unit,*)spice_validation_test%timestep,spice_validation_test%runtime
read(spice_model_spec_file_unit,*)spice_validation_test%risetime,spice_validation_test%width
else
write(*,*)'Read character',ch
run_status='ERROR: the analysis type should be ac or transient'
CALL write_program_status()
STOP 1
end if
! read the output conductor number and end number
read(spice_model_spec_file_unit,*) ! comment line
! see if we have one or two conductors specified as well as the reference
! read the next line into a string then read from there.
read(spice_model_spec_file_unit,'(A)')line
read(line,*,ERR=1000,END=1000)spice_validation_test%output_conductor, &
spice_validation_test%output_conductor_ref, &
spice_validation_test%output_end
GOTO 1010
1000 CONTINUE
read(line,*,ERR=9020,END=9020)spice_validation_test%output_conductor, &
spice_validation_test%output_end
spice_validation_test%output_conductor_ref=tot_n_conductors
1010 CONTINUE
! check that the conductor numbers are in the appropriate range
if ( (spice_validation_test%output_conductor.LT.1).OR. &
(spice_validation_test%output_conductor.GT.tot_n_conductors) ) then
write(run_status,*)'ERROR: The output conductor number should be in the range 1 to ',tot_n_conductors
CALL write_program_status()
STOP 1
end if
if ( (spice_validation_test%output_conductor_ref.LT.1) .OR. &
(spice_validation_test%output_conductor_ref.GT.tot_n_conductors) ) then
write(run_status,*)'ERROR: The output conductor reference number should be in the range 1 to ',tot_n_conductors
CALL write_program_status()
STOP 1
end if
if ((spice_validation_test%output_end.NE.1).AND.(spice_validation_test%output_end.NE.2)) then
write(run_status,*)'ERROR: The transfer impedance coupling direction should be either 1 or 2'
CALL write_program_status()
STOP 1
end if
! read the output type (lin or dB)
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
read(spice_model_spec_file_unit,'(A2)')spice_validation_test%output_type
if ( (spice_validation_test%output_type.NE.'li').and.(spice_validation_test%output_type.NE.'dB') ) then
run_status='ERROR the output type for ac analysis should be lin or dB'
CALL write_program_status()
STOP 1
end if
else
spice_validation_test%output_type='li'
end if
end if ! run_validation_test
! Set deafult propagation correction transfer function fit information
spice_bundle_model%Fit_model_order=0
CALL reset_frequency_specification(spice_bundle_model%prop_corr_fit_freq_spec)
CALL set_up_frequency_specification(spice_bundle_model%prop_corr_fit_freq_spec)
! Read the optional propagation correction transfer function fit information
read(spice_model_spec_file_unit,*,IOSTAT=ierr)spice_bundle_model%Fit_model_order
if (ierr.NE.0) then
! Assume there is no filter fit information specified so move on to the next stage
backspace(spice_model_spec_file_unit)
goto 100
end if
write(*,*)'Reading the filter fit frequency range'
CALL read_and_set_up_frequency_specification(spice_bundle_model%prop_corr_fit_freq_spec,spice_model_spec_file_unit)
100 continue
! The file can contain flags to control the running of the software and the output
rewind(spice_model_spec_file_unit)
do
read(spice_model_spec_file_unit,'(A)',END=200,ERR=200)line
CALL convert_to_lower_case(line,line_length)
! Set flags according to the information at the end of the .spice_model_spec file
if (INDEX(line,'verbose').NE.0) verbose=.TRUE.
if (INDEX(line,'use_s_xfer').NE.0) use_s_xfer=.TRUE.
if (INDEX(line,'no_s_xfer').NE.0) use_s_xfer=.FALSE.
if (INDEX(line,'use_xie').NE.0) use_Xie=.TRUE.
if (INDEX(line,'no_xie').NE.0) use_Xie=.FALSE.
if (INDEX(line,'use_ltra').NE.0) use_LTRA=.TRUE.
if (INDEX(line,'no_ltra').NE.0) use_LTRA=.FALSE.
if (INDEX(line,'use_high_freq_zt_model').NE.0) high_freq_Zt_model=.TRUE.
if (INDEX(line,'no_high_freq_zt_model').NE.0) high_freq_Zt_model=.FALSE.
if (INDEX(line,'plot_real').NE.0) plot_real=.TRUE.
if (INDEX(line,'plot_mag').NE.0) plot_real=.FALSE.
if (INDEX(line,'no_fasthenry').NE.0) use_FastHenry=.FALSE.
if (INDEX(line,'use_fasthenry').NE.0) then
use_FastHenry=.TRUE.
if (INDEX(line,'zc_validation').NE.0) then
use_zc_validation=.TRUE.
write(*,*)'SET: use_zc_validation'
else
write(*,*)'NOT set: use_zc_validation'
end if
end if
if (INDEX(line,'no_lossy_hf_modes').NE.0) use_lossy_hf_modes=.FALSE.
if (INDEX(line,'use_lossy_hf_modes').NE.0) use_lossy_hf_modes=.TRUE.
if (INDEX(line,'use_analytic_i').NE.0) run_validation_test_Vbased=.FALSE.
if (INDEX(line,'use_analytic_v').NE.0) run_validation_test_Vbased=.TRUE.
if (INDEX(line,'plot_propagation_correction_filter_fit_data').NE.0) plot_propagation_correction_filter_fit_data=.TRUE.
if (INDEX(line,'min_delay').NE.0) then
! Redefine minimum delay allowed for transmission lines in the sub-circuit models.
! Transmission lines with delays less than this value are dealt with in a different manner.
read(spice_model_spec_file_unit,*,END=200,ERR=200)min_delay
! set all transmission line minimum delays to this value
ZT_min_delay = min_delay
Einc_min_delay = min_delay
Tz_min_delay = min_delay
end if
if (INDEX(line,'rsmall').NE.0) then
! Redefine minimum resistance value in the sub-circuit model. Resistances less than this value are replaced by this value.
read(spice_model_spec_file_unit,*,END=200,ERR=200)Rsmall
end if
end do ! continue until all flags are read - indicated by an end of file.
200 CONTINUE
CLOSE(unit=spice_model_spec_file_unit)
if (verbose) then
write(*,*)'Closed file:',trim(filename)
end if
! Finished reading the .spice_model_spec file
! Create the spice subcircuit circuit model of the multi-conductor transmission line
do spice_version=1,3 ! Loop over all three spice versions supported
! set the file extensions for each of the spice versions
if (spice_version.EQ.ngspice) then
spice_model_file_extn =ngspice_spice_model_file_extn
symbol_file_extn=symbol_file_extn_NGspice
else if (spice_version.EQ.LTspice) then
spice_model_file_extn =LTspice_spice_model_file_extn
symbol_file_extn=symbol_file_extn_LTspice
else if (spice_version.EQ.Pspice) then
spice_model_file_extn =Pspice_spice_model_file_extn
! note: no symbol is produced here for Pspice
end if ! spice version
if (verbose) write(*,*)'CALLING: create_spice_subcircuit_model'
CALL create_spice_subcircuit_model(spice_bundle_model)
! Create the spice schematic symbol for the multi-conductor transmission line
! Note that there is no process here for Pspice symbols
! The process for Pspice is to load the .lib file in the Pspice model editor
! and create the symbol there.
if (verbose) write(*,*)'CALLING: create_spice_subcircuit_symbol'
if (spice_version.EQ.ngspice) then
CALL create_spice_subcircuit_symbol_NGspice(spice_bundle_model)
else if (spice_version.EQ.LTspice) then
CALL create_spice_subcircuit_symbol_LTspice(spice_bundle_model)
end if ! spice version
end do ! next spice version
if (run_validation_test) then
! Create the analytic and circuit models for solution of validation test case: i.e. a model of the
! terminations and link to the now existing spice subcircuit model of the multi-conductor
! transmission line and then add the analysis type information
! Analytic solution of validation test case
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
if (use_zc_validation) then
if (verbose) write(*,*)'CALLING: frequency_domain_analysis using FastHenry2 impedance matrices'
CALL frequency_domain_analysis_FH2(spice_bundle_model,spice_validation_test)
if (verbose) write(*,*)'FINISHED: frequency_domain_analysis using FastHenry2 impedance matrices'
else
if (verbose) write(*,*)'CALLING: frequency_domain_analysis'
CALL frequency_domain_analysis(spice_bundle_model,spice_validation_test)
if (verbose) write(*,*)'FINISHED: frequency_domain_analysis'
end if
else
if (verbose) write(*,*)'CALLING: time_domain_analysis'
CALL time_domain_analysis(spice_bundle_model,spice_validation_test)
if (verbose) write(*,*)'FINISHED: time_domain_analysis'
end if
! Create the spice subcircuit circuit model of the multi-conductor transmission line
do spice_version=1,3 ! Loop over all three spice versions supported
! set the file extensions for each of the spice versions
if (spice_version.EQ.ngspice) then
spice_model_file_extn =ngspice_spice_model_file_extn
test_circuit_file_extn=ngspice_test_circuit_file_extn
else if (spice_version.EQ.LTspice) then
spice_model_file_extn =LTspice_spice_model_file_extn
test_circuit_file_extn=LTspice_test_circuit_file_extn
else if (spice_version.EQ.Pspice) then
spice_model_file_extn =Pspice_spice_model_file_extn
test_circuit_file_extn=Pspice_test_circuit_file_extn
end if ! spice version
if (verbose) write(*,*)'CALLING: create_spice_validation_test_circuit'
CALL create_spice_validation_test_circuit(spice_bundle_model,spice_validation_test)
end do ! next spice version
end if ! run_validation_test
! Deallocate memory
CALL deallocate_spice_cable_bundle(spice_bundle_model)
CALL deallocate_spice_validation_test(spice_validation_test)
CALL deallocate_frequency_specification(spice_bundle_model%prop_corr_fit_freq_spec)
CALL deallocate_frequency_specification(spice_validation_test%analysis_freq_spec)
! finish up
run_status='Finished_Correctly'
CALL write_program_status()
STOP
9020 CONTINUE
write(run_status,*)'Error reading cable output condcutor(s) and end number'
CALL write_program_status()
STOP 1
9030 CONTINUE
write(run_status,*)'Error reading voltage sources at end 1, conductor number ',i
CALL write_program_status()
STOP 1
9040 CONTINUE
write(run_status,*)'Error reading termination resistances at end 1, conductor number ',i
CALL write_program_status()
STOP 1
9050 CONTINUE
write(run_status,*)'Error reading voltage sources at end 2, conductor number ',i
CALL write_program_status()
STOP 1
9060 CONTINUE
write(run_status,*)'Error reading termination resistances at end 2, conductor number ',i
CALL write_program_status()
STOP 1
END PROGRAM spice_cable_bundle_model_builder