!
! 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:
! SUBROUTINE create_spice_validation_test_circuit
!
! NAME
! create_spice_validation_test_circuit
!
! AUTHORS
! Chris Smartt
!
! DESCRIPTION
! This subroutine creates the Spice circuit model for the cable bundle
! with the resistive terminations and voltage sources and the
! simulation parameters i.e. a ready to run circuit file.
!
! The process is as follows:
! STAGE 1: Open the circuit file, allocate memory and set up the node numbering
! STAGE 2: set up the circuit element names
! STAGE 3: write circuit elements to file
! STAGE 3a: write circuit excitation voltage sources to file
! STAGE 3b: write termination impedance networks
! STAGE 3c: write incident field excitation source if required
! STAGE 3d: write link to transmission line sub-circuit model
! STAGE 3e: write circuit outputs to file taking into accout the different spice syntaxes for output specifications
! STAGE 4: close file and deallocate memory
!
! COMMENTS
! STAGE_1 Ngspice only
! STAGE_4 Ngspice, Pspice and LTspice
!
! HISTORY
!
! started 9/12/2015 CJS: STAGE_1 developments
! 22/4/2016 CJS: STAGE_4 developments: we can't use a common reference node at both ends now due to the d.c. resistances added into the
! transmission line sub-circuit so it has been changed
! 15/6/2016 CJS: Incident field excitation requires a voltage to be supplied to two additional terminals on the multi-conductor sub-circuit
! interface to supply the incident field source function
! 24/8/2016 CJS: Change the writing format for the transmission line model subcircuit to remove long lines (this is a problem for Pspice)
! 12/3/2018 CJS: Add more header information about SACAMOS
!
!
SUBROUTINE create_spice_validation_test_circuit(spice_bundle_model,spice_validation_test)
USE type_specifications
USE general_module
USE constants
USE cable_module
USE cable_bundle_module
USE spice_cable_bundle_module
IMPLICIT NONE
! variables passed to the subroutine
TYPE(spice_model_specification_type),intent(IN) :: spice_bundle_model ! spice bundle model information
TYPE(spice_validation_test_type),intent(IN) :: spice_validation_test ! spice validation test circuit information
! local variables
character(len=filename_length) :: filename
character(len=filename_length) :: spice_subcircuit_filename
integer :: n_conductors
! node numbering and component name stuff
integer :: node
! variables for external circuit, end 1
integer :: end1_reference_node
integer,allocatable :: Vs_end1_nodes(:) ! conductor based end 1 voltage list
integer,allocatable :: R_end1_nodes(:) ! conductor based end 1 resistance list
character(len=spice_name_length),allocatable :: Vs_end1_name(:) ! conductor based end 1 voltage source name list
character(len=spice_name_length),allocatable :: R_end1_name(:) ! conductor based end 1 resistance name list
! variables for external circuit, end 2
integer :: end2_reference_node
integer,allocatable :: Vs_end2_nodes(:) ! conductor based end 2 voltage list
integer,allocatable :: R_end2_nodes(:) ! conductor based end 2 resistance list
character(len=spice_name_length),allocatable :: Vs_end2_name(:) ! conductor based end 2 voltage source name list
character(len=spice_name_length),allocatable :: R_end2_name(:) ! conductor based end 2 resistance name list
! variables for incident field excitation source if requuired
integer :: Einc_node1
integer :: Einc_node2
character(len=spice_name_length) :: Einc_name
integer :: output_node,output_reference_node
character(len=spice_name_length) :: output_node_name
character(len=spice_name_length) :: output_node_name2
character(len=spice_name_length) :: name1
character(len=spice_name_length) :: name2
integer,allocatable :: node_list(:)
! Resistance value to write
real(dp) :: Rvalue
! loop variables
integer :: row,col
integer :: i
! START
! STAGE1: Open the circuit file, allocate memory and set up the node numbering
! open the file for the spice validation model - this goes in the current working directory...
filename=trim(spice_bundle_model%spice_model_name)//test_circuit_file_extn
OPEN(unit=test_circuit_file_unit,file=filename)
write(*,*)'Opened file:',trim(filename)
! Allocate memory
n_conductors=spice_bundle_model%bundle%tot_n_conductors
ALLOCATE( Vs_end1_nodes(n_conductors) )
ALLOCATE( R_end1_nodes(n_conductors) )
ALLOCATE( Vs_end1_name(n_conductors) )
ALLOCATE( R_end1_name(n_conductors) )
ALLOCATE( Vs_end2_nodes(n_conductors) )
ALLOCATE( R_end2_nodes(n_conductors) )
ALLOCATE( Vs_end2_name(n_conductors) )
ALLOCATE( R_end2_name(n_conductors) )
! set up the termination circuit nodes first, source end then load end.
node=0
end1_reference_node=node ! this is the reference node for end 1 of the circuit (and the global reference node)
node=node+1
end2_reference_node=node ! this is the reference node for end 2 of the circuit
do row=1,n_conductors
node=node+1
Vs_end1_nodes(row)=node
end do
do row=1,n_conductors ! We cannot now use the same reference at both ends
node=node+1
Vs_end2_nodes(row)=node
end do
do row=1,n_conductors
node=node+1
R_end1_nodes(row)=node
end do
do row=1,n_conductors
node=node+1
R_end2_nodes(row)=node
end do
if (spice_bundle_model%include_incident_field) then
node=node+1
Einc_node1=node
Einc_node2=end1_reference_node ! i.e. the global reference node for the external circuit
end if ! include_incident_field
! STAGE 2: set up the circuit element names
do row=1,n_conductors
name1='VS_'
CALL add_integer_to_string(name1,row,Vs_end1_name(row))
end do
do row=1,n_conductors
name1='RS_'
CALL add_integer_to_string(name1,row,R_end1_name(row))
end do
do row=1,n_conductors
name1='VL_'
CALL add_integer_to_string(name1,row,Vs_end2_name(row))
end do
do row=1,n_conductors
name1='RL_'
CALL add_integer_to_string(name1,row,R_end2_name(row))
end do
if (spice_bundle_model%include_incident_field) then
Einc_name='V_Einc'
end if ! include_incident_field
! STAGE 3: write circuit elements to file
if (spice_version.EQ.ngspice) then
write(test_circuit_file_unit,'(A)')'Ngspice multi-conductor transmission line validation model'
else if (spice_version.EQ.LTspice) then
write(test_circuit_file_unit,'(A)')'LTspice multi-conductor transmission line validation model'
else if (spice_version.EQ.Pspice) then
write(test_circuit_file_unit,'(A)')'Pspice multi-conductor transmission line validation model'
end if ! spice version
write(test_circuit_file_unit,'(A)') '*'
write(test_circuit_file_unit,'(A)') '* Created by SACAMOS (State-of-the-Art CAble MOdels for Spice) '
write(test_circuit_file_unit,'(A,A)')'* Spice cable model builder ',trim(SPICE_CABLE_MODEL_BUILDER_version)
write(test_circuit_file_unit,'(A)') '* www.sacamos.org'
write(test_circuit_file_unit,'(A)') '*'
write(test_circuit_file_unit,'(A)')'* Voltage sources at end 1'
! STAGE 3a: write circuit excitation to file taking into accout the different spice syntaxes for output specifications
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
do row=1,n_conductors
! could specify magnitude AND phase here but use specified amplitude and set phase to 0 at the moment
write(test_circuit_file_unit,'(A20,2I6,A4,2ES16.6)')Vs_end1_name(row),Vs_end1_nodes(row),end1_reference_node, &
' AC ',spice_validation_test%Vs_end1(row),0.0
end do
else if (spice_validation_test%analysis_type.EQ.analysis_type_TRANS) then
do row=1,n_conductors
write(test_circuit_file_unit,'(A20,2I6,A,5ES16.6,A)')Vs_end1_name(row),Vs_end1_nodes(row),end1_reference_node, &
' EXP( 0.0 ',spice_validation_test%Vs_end1(row),0.0,spice_validation_test%risetime, &
spice_validation_test%width,spice_validation_test%risetime,' )'
end do
end if
write(test_circuit_file_unit,'(A)')'* Voltage sources at end 2'
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
do row=1,n_conductors
! could specify magnitude AND phase here but use specified amplitude and set phase to 0 at the moment
write(test_circuit_file_unit,'(A20,2I6,A4,2ES16.6)')Vs_end2_name(row),Vs_end2_nodes(row),end2_reference_node, &
' AC ',spice_validation_test%Vs_end2(row),0.0
end do
else if (spice_validation_test%analysis_type.EQ.analysis_type_TRANS) then
do row=1,n_conductors
write(test_circuit_file_unit,'(A20,2I6,A,5ES16.6,A)')Vs_end2_name(row),Vs_end2_nodes(row),end2_reference_node, &
' EXP( 0.0 ',spice_validation_test%Vs_end2(row),0.0,spice_validation_test%risetime, &
spice_validation_test%width,spice_validation_test%risetime,' )'
end do
end if
! STAGE 3b: write termination impedance networks
write(test_circuit_file_unit,'(A)')'* Impedance network at end 1'
! note that the source impedance could be complex in the subroutine call - assumes a resistive diagonal matrix here...
do row=1,n_conductors
Rvalue=max(Rsmall,spice_validation_test%R_end1(row))
write(test_circuit_file_unit,'(A20,2I6,ES16.6)')R_end1_name(row),R_end1_nodes(row),Vs_end1_nodes(row),Rvalue
end do
write(test_circuit_file_unit,'(A)')'* Impedance network at end 2'
! note that the load impedance could be complex in the subroutine call - assumes a resistive diagonal matrix here...
do row=1,n_conductors
Rvalue=max(Rsmall,spice_validation_test%R_end2(row))
write(test_circuit_file_unit,'(A20,2I6,ES16.6)')R_end2_name(row),R_end2_nodes(row),Vs_end2_nodes(row),Rvalue
end do
! STAGE 3c: write incident field excitation source if required
if (spice_bundle_model%include_incident_field) then
write(test_circuit_file_unit,'(A)')'* Incident field excitation source'
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
! could specify magnitude AND phase here but use specified amplitude and set phase to 0 at the moment
write(test_circuit_file_unit,'(A20,2I6,A4,2ES16.6)')Einc_name,Einc_node1,Einc_node2, &
' AC ',spice_bundle_model%Eamplitude,0.0
else if (spice_validation_test%analysis_type.EQ.analysis_type_TRANS) then
write(test_circuit_file_unit,'(A20,2I6,A,5ES16.6,A)')Einc_name,Einc_node1,Einc_node2, &
' EXP( 0.0 ',spice_bundle_model%Eamplitude,0.0,spice_validation_test%risetime, &
spice_validation_test%width,spice_validation_test%risetime,' )'
end if
! include a resistance in series with the incident field voltage source to avoid a 'dangling' node
write(test_circuit_file_unit,'(A7,2I6,A4)')'R_Einc ',Einc_node1,Einc_node2,' 1E6'
end if ! include_incident_field
! Link to transmission line sub-circuit
write(test_circuit_file_unit,'(A)')'* Link to transmission line sub-circuit'
! note: include voltage reference nodes now
ALLOCATE( node_list(n_conductors) )
write(test_circuit_file_unit,'(A)')'xtransmission_line'
node_list(1:n_conductors)=R_end1_nodes(1:n_conductors)
CALL write_long_node_list(n_conductors,node_list,max_spice_line_length,test_circuit_file_unit)
node_list(1:n_conductors)=R_end2_nodes(1:n_conductors)
CALL write_long_node_list(n_conductors,node_list,max_spice_line_length,test_circuit_file_unit)
if (spice_bundle_model%include_incident_field) then
write(test_circuit_file_unit,'(A,2I6)')'+',Einc_node1,Einc_node2
end if
write(test_circuit_file_unit,'(A,A)')'+',trim(spice_bundle_model%spice_model_name)
spice_subcircuit_filename=trim(MOD_spice_bundle_lib_dir)//trim(spice_bundle_model%spice_model_name)//spice_model_file_extn
! include the transmission line subcircuit file here.
write(test_circuit_file_unit,'(A)')'*'
write(test_circuit_file_unit,'(A,A)')'.INCLUDE ',trim(spice_subcircuit_filename)
write(test_circuit_file_unit,'(A)')'*'
! STAGE 3e: write circuit outputs to file taking into accout the different spice syntaxes for output specifications
! work out the output voltage node number
if (spice_validation_test%output_end.eq.1) then
output_node =R_end1_nodes(spice_validation_test%output_conductor)
output_reference_node =R_end1_nodes(spice_validation_test%output_conductor_ref)
else
output_node =R_end2_nodes(spice_validation_test%output_conductor)
output_reference_node =R_end2_nodes(spice_validation_test%output_conductor_ref)
end if
if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then
! log frequency output
if (spice_validation_test%analysis_freq_spec%freq_range_type.EQ.'log') then
write(test_circuit_file_unit,'(A,I10,2ES16.6)')'.AC DEC ', &
NINT(spice_validation_test%analysis_freq_spec%n_frequencies/ &
log10(spice_validation_test%analysis_freq_spec%fmax/spice_validation_test%analysis_freq_spec%fmin)), &
spice_validation_test%analysis_freq_spec%fmin,spice_validation_test%analysis_freq_spec%fmax
else
! linear frequency output
write(test_circuit_file_unit,'(A,I10,2ES16.6)')'.AC LIN ', &
spice_validation_test%analysis_freq_spec%n_frequencies, &
spice_validation_test%analysis_freq_spec%fmin, &
spice_validation_test%analysis_freq_spec%fmax
end if ! frequency range type
write(test_circuit_file_unit,'(A)')'*'
if (spice_version.EQ.Pspice) then
name1='V('
CALL add_integer_to_string(name1,output_node,name2)
if (spice_validation_test%output_end.eq.2) then
name1=trim(name2)//','
CALL add_integer_to_string(name1,output_reference_node,name2)
end if
output_node_name=trim(name2)//')'
name1='VP('
CALL add_integer_to_string(name1,output_node,name2)
if (spice_validation_test%output_end.eq.2) then
name1=trim(name2)//','
CALL add_integer_to_string(name1,output_reference_node,name2)
end if
output_node_name2=trim(name2)//')'
write(test_circuit_file_unit,'(A,A,A,A)')'.PRINT ac ',trim(output_node_name),' ',trim(output_node_name2)
else ! ngspice or LTspice
if (spice_validation_test%output_type.EQ.'li') then
if (plot_real) then
name1='V('
else
name1='VM('
end if
else if (spice_validation_test%output_type.EQ.'dB') then
name1='VDB('
end if
CALL add_integer_to_string(name1,output_node,name2)
name1=trim(name2)//','
CALL add_integer_to_string(name1,output_reference_node,name2)
output_node_name=trim(name2)//')'
write(test_circuit_file_unit,'(A,A)')'.PRINT ac ',trim(output_node_name)
end if
if ( (spice_version.EQ.LTspice) .OR.(spice_version.EQ.Pspice) ) then
write(test_circuit_file_unit,'(A)')'.PROBE'
end if
else
! Transient simulation
if (spice_validation_test%output_type.EQ.'li') then
name1='V('
else if (spice_validation_test%output_type.EQ.'dB') then
name1='VDB('
end if
CALL add_integer_to_string(name1,output_node,name2)
name1=trim(name2)//','
CALL add_integer_to_string(name1,output_reference_node,name2)
output_node_name=trim(name2)//')'
if (spice_version.NE.LTspice) then
write(test_circuit_file_unit,'(A,2ES16.6)')'.TRAN ', &
spice_validation_test%timestep,spice_validation_test%runtime
else
! Add a timestep limit for LTpsice
write(test_circuit_file_unit,'(A,2ES16.6,A,ES16.6)')'.TRAN ', &
spice_validation_test%timestep,spice_validation_test%runtime,' 0.0 ',spice_validation_test%timestep/10d0
end if
write(test_circuit_file_unit,'(A)')'*'
write(test_circuit_file_unit,'(A,A)')'.PRINT tran ',output_node_name
if (spice_version.EQ.Pspice) then
write(test_circuit_file_unit,'(A)')'*'
write(test_circuit_file_unit,'(A)')'.PROBE'
end if
end if
write(test_circuit_file_unit,'(A)')'*'
write(test_circuit_file_unit,'(A)')'*'
write(test_circuit_file_unit,'(A)')'.END'
8100 format(10I4)
! STAGE 4: Close file and Deallocate memory
CLOSE(unit=test_circuit_file_unit)
write(*,*)'Closed file:',trim(filename)
DEALLOCATE( Vs_end1_nodes)
DEALLOCATE( R_end1_nodes )
DEALLOCATE( Vs_end1_name )
DEALLOCATE( R_end1_name )
DEALLOCATE( Vs_end2_nodes )
DEALLOCATE( R_end2_nodes )
DEALLOCATE( Vs_end2_name )
DEALLOCATE( R_end2_name )
RETURN
END SUBROUTINE create_spice_validation_test_circuit