Blame view

SRC/CREATE_SPICE_CIRCUIT_MODEL/write_spice_subcircuit_header.F90 7.16 KB
fe64b32b   Chris Smartt   Update file heade...
1
2
!
! This file is part of SACAMOS, State of the Art CAble MOdels for Spice. 
886c558b   Steve Greedy   SACAMOS Public Re...
3
4
5
! It was developed by the University of Nottingham and the Netherlands Aerospace 
! Centre (NLR) for ESA under contract number 4000112765/14/NL/HK.
! 
fe64b32b   Chris Smartt   Update file heade...
6
! Copyright (C) 2016-2018 University of Nottingham
886c558b   Steve Greedy   SACAMOS Public Re...
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
! 
! 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 <http://www.gnu.org/licenses/>.
! 
! 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 <http://www.gnu.org/licenses/>.
! 
! The University of Nottingham can be contacted at: ggiemr@nottingham.ac.uk
!
fe64b32b   Chris Smartt   Update file heade...
28
!
886c558b   Steve Greedy   SACAMOS Public Re...
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
! 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
189467e4   Steve Greedy   First Public Release
68
69
70
!     18/10/2017 CJS: Improve the conductor labelling based on revised cable and bundle conductor labels
!     16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
!     12/3/2018 CJS: Add more header information about SACAMOS
886c558b   Steve Greedy   SACAMOS Public Re...
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
!
  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
189467e4   Steve Greedy   First Public Release
108
  integer :: conductor
886c558b   Steve Greedy   SACAMOS Public Re...
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137

  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
189467e4   Steve Greedy   First Public Release
138
139
140
141
142
143
   
  write(spice_model_file_unit,'(A)')  '*'
  write(spice_model_file_unit,'(A)')  '* Created by SACAMOS (State-of-the-Art CAble MOdels for Spice) '
  write(spice_model_file_unit,'(A,A)')'* Spice cable model builder ',trim(SPICE_CABLE_MODEL_BUILDER_version)
  write(spice_model_file_unit,'(A)')  '* www.sacamos.org'
  write(spice_model_file_unit,'(A)')  '*'
886c558b   Steve Greedy   SACAMOS Public Re...
144
145
146
147
148
149
150
151
  
  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
189467e4   Steve Greedy   First Public Release
152
    
886c558b   Steve Greedy   SACAMOS Public Re...
153
  CALL write_spice_comment('End 1 nodes:')
189467e4   Steve Greedy   First Public Release
154
155
156
  do conductor=1,tot_n_conductors
    write(spice_model_file_unit,'(A7,I3,A,I3,A,A,A,A,A,A,I3)')'* node:',external_end1_nodes(conductor),   &
                                                              trim(spice_cable_bundle_model%bundle%conductor_label(conductor))
886c558b   Steve Greedy   SACAMOS Public Re...
157
  
189467e4   Steve Greedy   First Public Release
158
  end do
886c558b   Steve Greedy   SACAMOS Public Re...
159
160
  
  CALL write_spice_comment('End 2 nodes:')
189467e4   Steve Greedy   First Public Release
161
162
163
  do conductor=1,tot_n_conductors
    write(spice_model_file_unit,'(A7,I3,A,I3,A,A,A,A,A,A,I3)')'* node:',external_end2_nodes(conductor),   &
                                                              trim(spice_cable_bundle_model%bundle%conductor_label(conductor))
886c558b   Steve Greedy   SACAMOS Public Re...
164
  
189467e4   Steve Greedy   First Public Release
165
  end do
886c558b   Steve Greedy   SACAMOS Public Re...
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
  
  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