! This file is part of SACAMOS, State of the Art CAble MOdels in 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-2017 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 write_spice_subcircuit_header ! ! NAME ! write_spice_subcircuit_header ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! Create the node numbering for the external conductors and ! write the subcircuit header ! ! INPUTS REQUIRED ! 1. The total number of conductors ! 2. The first free node available ! 3. Flag indicating whether an incident field excitation is present ! 4. Numbers for the incident field excitation termination nodes ! ! OUTPUTS ! 1. The subcircuit header information including the termination nodes at both ends ! the subcircuit file ! 2. The termination nodes at both ends are created in the subroutine and ! are returned to the calling process ! ! COMMENTS ! ! The reference node is no longer included here, it goes the other side of the d.c. resistance on the reference conductor ! ! We could maybe include comments to include some meaningful labelling of the external conductor numbers ! i.e. relate them to individual cables and conductors within them. ! ! HISTORY ! ! STAGE 2 developments started 2/2/2016 ! STAGE 4 developments started 22/4/2016 ! 24/8/2016 CJS: Change the writing format for the transmission line model subcircuit to remove long lines (this is a problem for Pspice) ! 4/8/2017 CJS: use n_conductors_without_ground_plane rather than n_conductors when ! writing the cable information ! SUBROUTINE write_spice_subcircuit_header(spice_cable_bundle_model, & next_free_node,tot_n_conductors,external_end1_nodes,external_end2_nodes, & include_incident_field,Einc_node1,Einc_node2) USE type_specifications USE general_module 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_cable_bundle_model integer,intent(INOUT) :: next_free_node ! spice node number counter integer,intent(IN) :: tot_n_conductors integer,intent(INOUT) :: external_end1_nodes(1:tot_n_conductors) ! list of the external nodes at end 1 integer,intent(INOUT) :: external_end2_nodes(1:tot_n_conductors) ! list of the external nodes at end 2 logical,intent(IN) :: include_incident_field ! flag indicating whether and incident field excitation source is required integer,intent(IN) :: Einc_node1 ! node numbers for the external incident field excitation voltage integer,intent(IN) :: Einc_node2 ! local variables character(len=line_length) :: bundle_name character(len=line_length) :: spice_model_name ! string used to generate comments character(len=max_spice_line_length) :: comment ! variables to assemble the conductor label integer :: n_cables,cable,n_conductors,conductor,conductor_count character(LEN=line_length) :: cable_name character(LEN=line_length) :: cable_type_string integer :: i ! loop variable ! START bundle_name=spice_cable_bundle_model%bundle%bundle_name spice_model_name=spice_cable_bundle_model%spice_model_name ! set the external connection node numbers. do i=1,tot_n_conductors external_end1_nodes(i)=next_free_node next_free_node=next_free_node+1 end do do i=1,tot_n_conductors external_end2_nodes(i)=next_free_node next_free_node=next_free_node+1 end do ! write some general information into the spice subcircuit file if (spice_version.EQ.ngspice) then write(spice_model_file_unit,'(A)')'* Ngspice multi-conductor transmission line model' else if (spice_version.EQ.LTspice) then write(spice_model_file_unit,'(A)')'* LTspice multi-conductor transmission line model' else if (spice_version.EQ.Pspice) then write(spice_model_file_unit,'(A)')'* Pspice multi-conductor transmission line model' end if ! spice version write(spice_model_file_unit,'(A,A)')'* Created by Spice cable model builder ',trim(SPICE_CABLE_MODEL_BUILDER_version) write(comment,'(A,A)')'* Cable bundle name: ',trim(bundle_name) ! Write the transmission line subcircuit interface information CALL write_spice_comment('Transmission line subcircuit') ! write the node labels here ! n_cables=spice_cable_bundle_model%bundle%n_cables n_cables=spice_cable_bundle_model%bundle%n_cables_without_ground_plane CALL write_spice_comment('End 1 nodes:') conductor_count=0 do cable=1,n_cables n_conductors=spice_cable_bundle_model%bundle%cable(cable)%tot_n_conductors cable_name=spice_cable_bundle_model%bundle%cable(cable)%cable_name cable_type_string=spice_cable_bundle_model%bundle%cable(cable)%cable_type_string write(*,*)'Cable number',cable,' of',n_cables,' nc=',n_conductors do conductor=1,n_conductors conductor_count=conductor_count+1 write(spice_model_file_unit,'(A7,I3,A,I3,A,A,A,A,A,A,I3)')'* node:',external_end1_nodes(conductor_count), & ' cable number:',cable,' type:',trim(cable_type_string), & ' name:',trim(cable_name),' ',' conductor number',conductor end do ! next conductor in this cable end do ! next cable if (spice_cable_bundle_model%bundle%ground_plane_present) then conductor_count=conductor_count+1 write(spice_model_file_unit,'(A7,I3,A)')'* node:',external_end1_nodes(conductor_count),' Ground plane' end if CALL write_spice_comment('End 2 nodes:') conductor_count=0 do cable=1,n_cables n_conductors=spice_cable_bundle_model%bundle%cable(cable)%tot_n_conductors cable_name=spice_cable_bundle_model%bundle%cable(cable)%cable_name cable_type_string=spice_cable_bundle_model%bundle%cable(cable)%cable_type_string do conductor=1,n_conductors conductor_count=conductor_count+1 write(spice_model_file_unit,'(A7,I3,A,I3,A,A,A,A,A,A,I3)')'* node:',external_end2_nodes(conductor_count), & ' cable number:',cable,' type:',trim(cable_type_string), & ' name:',trim(cable_name),' ',' conductor number',conductor end do ! next conductor in this cable end do ! next cable if (spice_cable_bundle_model%bundle%ground_plane_present) then conductor_count=conductor_count+1 write(spice_model_file_unit,'(A7,I3,A)')'* node:',external_end2_nodes(conductor_count),' Ground plane' end if if (include_incident_field) then CALL write_spice_comment('Incident field function nodes:') write(spice_model_file_unit,'(A2,2I6)')'* ',Einc_node1,Einc_node2 end if write(spice_model_file_unit,'(A)')'*' write(spice_model_file_unit,'(A,A)')'.subckt ',trim(spice_model_name) CALL write_long_node_list(tot_n_conductors,external_end1_nodes,max_spice_line_length,spice_model_file_unit) CALL write_long_node_list(tot_n_conductors,external_end2_nodes,max_spice_line_length,spice_model_file_unit) if (include_incident_field) then write(spice_model_file_unit,'(A,2I6)')'+',Einc_node1,Einc_node2 end if END SUBROUTINE write_spice_subcircuit_header