Commit eba72ccde282a77c7a62d8a493e7b7a394e4b1b3
1 parent
ca8ab9e9
Exists in
proximity_effects
Use FastHenry2 impedance matrices in analytic MTL solution
Showing
6 changed files
with
828 additions
and
7 deletions
Show diff stats
SRC/MTL_ANALYTIC_SOLUTION/MTL_analytic_solution.F90
| ... | ... | @@ -29,6 +29,7 @@ |
| 29 | 29 | ! FILE CONTENTS (within include files) |
| 30 | 30 | ! |
| 31 | 31 | !frequency_domain_analysis.F90: SUBROUTINE frequency_domain_analysis |
| 32 | +!frequency_domain_analysis_FH2.F90: SUBROUTINE frequency_domain_analysis_FH2 | |
| 32 | 33 | !time_domain_analysis.F90: SUBROUTINE time_domain_analysis |
| 33 | 34 | !frequency_domain_MTL_solution.F90: SUBROUTINE frequency_domain_MTL_solution |
| 34 | 35 | !incident_field_excitation.F90: SUBROUTINE calc_incident_field_components |
| ... | ... | @@ -73,6 +74,8 @@ include 'modal_decomposition.F90' |
| 73 | 74 | |
| 74 | 75 | include 'frequency_domain_analysis.F90' |
| 75 | 76 | |
| 77 | +include 'frequency_domain_analysis_FH2.F90' | |
| 78 | + | |
| 76 | 79 | include 'time_domain_analysis.F90' |
| 77 | 80 | |
| 78 | 81 | include 'frequency_domain_MTL_solution.F90' | ... | ... |
SRC/MTL_ANALYTIC_SOLUTION/Makefile
| 1 | 1 | default: $(MTL_ANALYTIC_SOLUTION_OBJS) |
| 2 | 2 | # |
| 3 | 3 | $(OBJ_MOD_DIR)/%.o: %.F90 $(TYPE_SPEC_MODULE) $(CONSTANTS_MODULE) $(EISPACK_MODULE) $(MATHS_MODULE)\ |
| 4 | - frequency_domain_analysis.F90 frequency_domain_MTL_solution.F90 \ | |
| 4 | + frequency_domain_analysis.F90 frequency_domain_analysis_FH2.F90 frequency_domain_MTL_solution.F90 \ | |
| 5 | 5 | modal_decomposition_LC.F90 modal_decomposition.F90 \ |
| 6 | 6 | time_domain_analysis.F90 propagation_correction_filters.F90 incident_field_excitation.F90 |
| 7 | 7 | ... | ... |
SRC/MTL_ANALYTIC_SOLUTION/frequency_domain_analysis_FH2.F90
0 → 100644
| ... | ... | @@ -0,0 +1,644 @@ |
| 1 | +! | |
| 2 | +! This file is part of SACAMOS, State of the Art CAble MOdels for Spice. | |
| 3 | +! It was developed by the University of Nottingham and the Netherlands Aerospace | |
| 4 | +! Centre (NLR) for ESA under contract number 4000112765/14/NL/HK. | |
| 5 | +! | |
| 6 | +! Copyright (C) 2016-2018 University of Nottingham | |
| 7 | +! | |
| 8 | +! SACAMOS is free software: you can redistribute it and/or modify it under the | |
| 9 | +! terms of the GNU General Public License as published by the Free Software | |
| 10 | +! Foundation, either version 3 of the License, or (at your option) any later | |
| 11 | +! version. | |
| 12 | +! | |
| 13 | +! SACAMOS is distributed in the hope that it will be useful, but | |
| 14 | +! WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY | |
| 15 | +! or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License | |
| 16 | +! for more details. | |
| 17 | +! | |
| 18 | +! A copy of the GNU General Public License version 3 can be found in the | |
| 19 | +! file GNU_GPL_v3 in the root or at <http://www.gnu.org/licenses/>. | |
| 20 | +! | |
| 21 | +! SACAMOS uses the EISPACK library (in /SRC/EISPACK). EISPACK is subject to | |
| 22 | +! the GNU Lesser General Public License. A copy of the GNU Lesser General Public | |
| 23 | +! License version can be found in the file GNU_LGPL in the root of EISPACK | |
| 24 | +! (/SRC/EISPACK ) or at <http://www.gnu.org/licenses/>. | |
| 25 | +! | |
| 26 | +! The University of Nottingham can be contacted at: ggiemr@nottingham.ac.uk | |
| 27 | +! | |
| 28 | +! | |
| 29 | +! File Contents: | |
| 30 | +! SUBROUTINE frequency_domain_analysis_FH2 | |
| 31 | +! | |
| 32 | +! NAME | |
| 33 | +! frequency_domain_analysis_FH2 | |
| 34 | +! | |
| 35 | +! AUTHORS | |
| 36 | +! Chris Smartt | |
| 37 | +! | |
| 38 | +! DESCRIPTION | |
| 39 | +! This subroutine controls the analytic solution for the frequency domain analysis of | |
| 40 | +! multi-conductor transmission lines. | |
| 41 | +! The solution is obtained using the full dimension transmission line equations | |
| 42 | +! i.e. we are NOT using the weak form of transfer impedance coupling | |
| 43 | +! Note also that frequency dependent quantities are evaluated separately at | |
| 44 | +! each frequency of analysis, i.e. the frequency dependence of the solution is rigorous | |
| 45 | +! given only the frequency dependence of the dielectrics is modelled using impedance/ admittance | |
| 46 | +! matrices whose elements are rational frequency dependent filter functions. | |
| 47 | +! | |
| 48 | +! INPUTS: | |
| 49 | +! spice_bundle_model structure | |
| 50 | +! spice_validation_test structure | |
| 51 | +! | |
| 52 | +! OUTPUT | |
| 53 | +! analytic frequency domain termination voltage for the specified validation test case written to file | |
| 54 | +! | |
| 55 | +! COMMENTS | |
| 56 | +! STAGE_1: frequency independent parameter solution | |
| 57 | +! STAGE_2: multi-conductor solution | |
| 58 | +! STAGE_3: shielded cable solution | |
| 59 | +! STAGE_4: frequency dependent model | |
| 60 | +! STAGE_5: transfer impedance model | |
| 61 | +! | |
| 62 | +! HISTORY | |
| 63 | +! | |
| 64 | +! started 7/12/2015 CJS: STAGE_1 developments | |
| 65 | +! 24/03/2016 CJS: STAGE_3 developments -shielded cables | |
| 66 | +! 22/04/2016 CJS: STAGE_4 developments -frequency dependent model | |
| 67 | +! Include general conductor impedance model 12/05/2016 CJS | |
| 68 | +! Fix bug with conductor impedance contributions 12/05/2016 CJS | |
| 69 | +! 25/08/2016 CJS Include revised transfer impedance/ condcutor impedance model for shields | |
| 70 | +! 8/09/2016 CJS Correct the common mode/ differential mode loss terms for twisted pairs | |
| 71 | +! 13/10/2016 CJS Correct transfer impedance for multiple modes in external domain | |
| 72 | +! 7/3/2017 CJS: Add resistance and voltage source onto the reference coonductor | |
| 73 | +! 8/5/2017 CJS: Include references to Theory_Manual | |
| 74 | +! | |
| 75 | +! 26/10/2023 CJS: use FastHenry impedance matrix in analytic solution | |
| 76 | +! | |
| 77 | +SUBROUTINE frequency_domain_analysis_FH2(spice_bundle_model,spice_validation_test) | |
| 78 | + | |
| 79 | +USE type_specifications | |
| 80 | +USE general_module | |
| 81 | +USE constants | |
| 82 | +USE cable_module | |
| 83 | +USE cable_bundle_module | |
| 84 | +USE spice_cable_bundle_module | |
| 85 | +USE maths | |
| 86 | +USE frequency_spec | |
| 87 | + | |
| 88 | +IMPLICIT NONE | |
| 89 | + | |
| 90 | +! variables passed to subroutine | |
| 91 | + | |
| 92 | +TYPE(spice_model_specification_type),intent(IN):: spice_bundle_model ! Spice cable bundle model structure | |
| 93 | + | |
| 94 | +TYPE(spice_validation_test_type),intent(IN) :: spice_validation_test ! Spice validation circuit structure | |
| 95 | + | |
| 96 | +! local variables | |
| 97 | + | |
| 98 | +real(dp) :: f,w ! frequency and angular frequency | |
| 99 | +integer :: frequency_loop ! frequency loop variable | |
| 100 | + | |
| 101 | +integer :: dim ! dimension of matrix system to solve | |
| 102 | + | |
| 103 | +! domain based impedance and admittance matrices | |
| 104 | +complex(dp),allocatable :: Z_domain(:,:) | |
| 105 | +complex(dp),allocatable :: Y_domain(:,:) | |
| 106 | + | |
| 107 | +! domain based conductor impedance terms | |
| 108 | +complex(dp),allocatable ::Z_domain_conductor_impedance_correction(:,:) | |
| 109 | + | |
| 110 | +! Vectors and matrices used in the frequency domain solution of the transmission line equations with termination conditions | |
| 111 | +complex(dp),allocatable :: Vs1(:) | |
| 112 | +complex(dp),allocatable :: Z1(:,:) | |
| 113 | +complex(dp),allocatable :: Vs2(:) | |
| 114 | +complex(dp),allocatable :: Z2(:,:) | |
| 115 | + | |
| 116 | +complex(dp) :: Vout ! complex output voltage value | |
| 117 | + | |
| 118 | +! domain transformation matrices | |
| 119 | +complex(dp),allocatable :: MI(:,:) | |
| 120 | +complex(dp),allocatable :: MII(:,:) | |
| 121 | +complex(dp),allocatable :: MV(:,:) | |
| 122 | +complex(dp),allocatable :: MVI(:,:) | |
| 123 | + | |
| 124 | +! temporary working matrices | |
| 125 | +complex(dp),allocatable :: TM1(:,:) | |
| 126 | + | |
| 127 | +! temporary variables | |
| 128 | +integer :: conductor,inner_domain,outer_domain | |
| 129 | + | |
| 130 | +integer :: domain1,inner_domain1,outer_domain1 | |
| 131 | +integer :: conductor1,reference_conductor1 | |
| 132 | +integer :: domain_conductor1,domain_reference_conductor1 | |
| 133 | +logical :: is_shield1 | |
| 134 | + | |
| 135 | +integer :: domain2,inner_domain2,outer_domain2 | |
| 136 | +integer :: conductor2,reference_conductor2 | |
| 137 | +integer :: domain_conductor2,domain_reference_conductor2 | |
| 138 | +logical :: is_shield2 | |
| 139 | + | |
| 140 | +! conductor based impedance (loss) and transfer impedance model data | |
| 141 | +complex(dp) :: Zint_c ! conductor surface impedance | |
| 142 | +complex(dp) :: Zint_c_ref ! reference conductor surface impedance | |
| 143 | +real(dp) :: Rdc_c ! d.c. resistance of conductor | |
| 144 | +real(dp) :: Rdc_c_ref ! d.c. resistance of reference conductor | |
| 145 | +complex(dp) :: Zint_t ! conductor transfer impedance | |
| 146 | +complex(dp) :: Zint_t_ref ! reference conductor transfer impedance | |
| 147 | +real(dp) :: Rdc_t ! d.c. resistance of conductor (from transfer impedance) | |
| 148 | +real(dp) :: Rdc_t_ref ! d.c. resistance of reference conductor (from transfer impedance) | |
| 149 | + | |
| 150 | +! complex amplitude of incident field | |
| 151 | +complex(dp) :: Einc | |
| 152 | + | |
| 153 | +logical,allocatable :: is_shielded_flag(:) ! flags conductors which are not exposed to the incident field | |
| 154 | +integer :: shield_conductor ! temporary variable, shield conductor number for shielded conductors | |
| 155 | +real(dp),allocatable :: local_conductor_x_offset(:) ! x coordinate in bundle cross section of conductors | |
| 156 | +real(dp),allocatable :: local_conductor_y_offset(:) ! y coordinate in bundle cross section of conductors | |
| 157 | + | |
| 158 | +integer :: n_conductors_outer_domain ! for shield conductors, the number of conductors in the domain outside the shield | |
| 159 | +integer :: shield_conductor_number_in_outer_domain ! for shield conductors, the conductor number in the domain outside the shield | |
| 160 | + | |
| 161 | +! loop variables | |
| 162 | +integer :: row,col | |
| 163 | +integer :: i | |
| 164 | + | |
| 165 | +integer :: ierr ! error code for matrix inverse calls | |
| 166 | + | |
| 167 | +! FastHenry2 stuff... | |
| 168 | + | |
| 169 | +character(LEN=256) :: line | |
| 170 | +character(LEN=256) :: freq_and_dim_string | |
| 171 | + | |
| 172 | +integer :: local_line_length | |
| 173 | + | |
| 174 | +integer :: n_freq_in | |
| 175 | + | |
| 176 | +real(dp) :: freq | |
| 177 | +integer :: nrows,ncols,r,c | |
| 178 | + | |
| 179 | +complex(dp),allocatable :: Zc_in(:,:,:) | |
| 180 | +real(dp),allocatable :: freq_in(:) | |
| 181 | +real(dp),allocatable :: values(:),re,im | |
| 182 | + | |
| 183 | +integer :: loop,floop | |
| 184 | + | |
| 185 | + | |
| 186 | +! START | |
| 187 | + | |
| 188 | +! Open output file | |
| 189 | + open(unit=analytic_soln_file_unit,file=trim(analytic_soln_filename)) | |
| 190 | + | |
| 191 | +! write the file header line | |
| 192 | + if (spice_validation_test%analysis_freq_spec%freq_range_type.EQ.'log') then | |
| 193 | + write(analytic_soln_file_unit,'(A)')log_freq_header | |
| 194 | + else if (spice_validation_test%analysis_freq_spec%freq_range_type.EQ.'lin') then | |
| 195 | + write(analytic_soln_file_unit,'(A)')lin_freq_header | |
| 196 | + end if | |
| 197 | + | |
| 198 | + dim=spice_bundle_model%bundle%system_dimension | |
| 199 | + | |
| 200 | +! allocate memory | |
| 201 | + ALLOCATE( Z_domain(dim,dim) ) | |
| 202 | + ALLOCATE( Y_domain(dim,dim) ) | |
| 203 | + | |
| 204 | + ALLOCATE( Z_domain_conductor_impedance_correction(dim,dim) ) | |
| 205 | + | |
| 206 | + ALLOCATE( Vs1(dim) ) | |
| 207 | + ALLOCATE( Z1(dim,dim) ) | |
| 208 | + ALLOCATE( Vs2(dim) ) | |
| 209 | + ALLOCATE( Z2(dim,dim) ) | |
| 210 | + | |
| 211 | +! domain transformation matrices | |
| 212 | + ALLOCATE( MI(dim,dim) ) | |
| 213 | + ALLOCATE( MII(dim,dim) ) | |
| 214 | + ALLOCATE( MV(dim,dim) ) | |
| 215 | + ALLOCATE( MVI(dim,dim) ) | |
| 216 | + | |
| 217 | +! temporary working matrices | |
| 218 | + ALLOCATE( TM1(dim,dim) ) | |
| 219 | + | |
| 220 | + ALLOCATE( is_shielded_flag(1:dim+1) ) | |
| 221 | + ALLOCATE( local_conductor_x_offset(1:dim+1) ) | |
| 222 | + ALLOCATE( local_conductor_y_offset(1:dim+1) ) | |
| 223 | + | |
| 224 | +! loop over conductors to work out which are in shielded domains and which are in the external domain | |
| 225 | +! also get the position of the conductor in the bundle cross section for incident field excitation | |
| 226 | + | |
| 227 | + do i=1,dim+1 | |
| 228 | + if (spice_bundle_model%bundle%terminal_conductor_to_outer_domain(i).EQ.spice_bundle_model%bundle%tot_n_domains) then | |
| 229 | + is_shielded_flag(i)=.FALSE. | |
| 230 | + local_conductor_x_offset(i)=spice_bundle_model%bundle%conductor_x_offset(i) | |
| 231 | + local_conductor_y_offset(i)=spice_bundle_model%bundle%conductor_y_offset(i) | |
| 232 | + else | |
| 233 | + is_shielded_flag(i)=.TRUE. | |
| 234 | +! work out the conductor number of the shield | |
| 235 | + shield_conductor=spice_bundle_model%bundle%terminal_conductor_to_reference_terminal_conductor(i) | |
| 236 | +! shielded conductors pick up the coordinate of the shield for the purposes of incident field excitation | |
| 237 | + local_conductor_x_offset(i)=spice_bundle_model%bundle%conductor_x_offset(shield_conductor) | |
| 238 | + local_conductor_y_offset(i)=spice_bundle_model%bundle%conductor_y_offset(shield_conductor) | |
| 239 | + end if | |
| 240 | + | |
| 241 | + end do | |
| 242 | + | |
| 243 | +! build the termination specifications and convert to complex | |
| 244 | + Vs1(1:dim)=cmplx( spice_validation_test%Vs_end1(1:dim)-spice_validation_test%Vs_end1(dim+1) ) | |
| 245 | + Vs2(1:dim)=cmplx( spice_validation_test%Vs_end2(1:dim)-spice_validation_test%Vs_end2(dim+1) ) | |
| 246 | + | |
| 247 | + Z1(:,:) =cmplx( spice_validation_test%R_end1(dim+1) ) | |
| 248 | + Z2(:,:) =cmplx( spice_validation_test%R_end2(dim+1) ) | |
| 249 | + do i=1,dim | |
| 250 | + Z1(i,i) =Z1(i,i)+cmplx( spice_validation_test%R_end1(i) ) | |
| 251 | + Z2(i,i) =Z2(i,i)+cmplx( spice_validation_test%R_end2(i) ) | |
| 252 | + end do | |
| 253 | + | |
| 254 | +! Copy the domain transformation matrices and calculate the inverses | |
| 255 | + MI(:,:)=cmplx(spice_bundle_model%bundle%global_MI%mat(:,:)) | |
| 256 | + MV(:,:)=cmplx(spice_bundle_model%bundle%global_MV%mat(:,:)) | |
| 257 | + | |
| 258 | + if (verbose) write(*,*)'Invert MI' | |
| 259 | + ierr=0 ! set ierr=0 on input to matrix inverse to cause the program to stop if we have a singular matrix | |
| 260 | + CALL cinvert_Gauss_Jordan(MI,dim,MII,dim,ierr) | |
| 261 | + | |
| 262 | + if (verbose) then | |
| 263 | + write(*,*)'Transpose[MII]' | |
| 264 | + do row=1,dim | |
| 265 | + write(*,8000)(real(MII(col,row)),col=1,dim) | |
| 266 | + end do | |
| 267 | + | |
| 268 | + write(*,*)'[MV]' | |
| 269 | + do row=1,dim | |
| 270 | + write(*,8000)(real(MV(row,col)),col=1,dim) | |
| 271 | + end do | |
| 272 | +8000 format(20F4.1) | |
| 273 | + | |
| 274 | + end if ! verbose | |
| 275 | + | |
| 276 | + if (verbose) write(*,*)'Invert MV' | |
| 277 | + ierr=0 ! set ierr=0 on input to matrix inverse to cause the program to stop if we have a singular matrix | |
| 278 | + CALL cinvert_Gauss_Jordan(MV,dim,MVI,dim,ierr) | |
| 279 | + | |
| 280 | + | |
| 281 | + if (verbose) then | |
| 282 | + write(*,*) | |
| 283 | + write(*,*)' Processing frequency dependent impedance file from FastHenry2' | |
| 284 | + write(*,*) | |
| 285 | + end if | |
| 286 | + | |
| 287 | + OPEN(unit=fh2_output_file_unit,file='Zc.mat') | |
| 288 | + | |
| 289 | + do loop=1,2 | |
| 290 | + | |
| 291 | + n_freq_in=0 | |
| 292 | + | |
| 293 | +10 CONTINUE | |
| 294 | + read(fh2_output_file_unit,'(A)',END=1000,ERR=1000)line | |
| 295 | + if (line(1:32).NE.'Impedance matrix for frequency =') GOTO 10 | |
| 296 | + | |
| 297 | +! if we get here then we have some impedance matrix data to read | |
| 298 | +! write(*,*)'Found impedance matrix:',trim(line) | |
| 299 | + | |
| 300 | +! increase the number of frequencies for which we have an impedance matrix | |
| 301 | + n_freq_in=n_freq_in+1 | |
| 302 | + | |
| 303 | + local_line_length=len(trim(line)) | |
| 304 | + freq_and_dim_string=line(33:local_line_length) | |
| 305 | + | |
| 306 | +! write(*,*)'reading matrix for:',trim(freq_and_dim_string) | |
| 307 | + | |
| 308 | +! replace the 'x' by a space then read the frequency, nrows and ncols | |
| 309 | + local_line_length=len(trim(freq_and_dim_string)) | |
| 310 | + do i=1,local_line_length | |
| 311 | + if (freq_and_dim_string(i:i).EQ.'x') freq_and_dim_string(i:i)=' ' | |
| 312 | + end do | |
| 313 | + | |
| 314 | +! write(*,*)'data string:',trim(freq_and_dim_string) | |
| 315 | + | |
| 316 | + read(freq_and_dim_string,*)freq,nrows,ncols | |
| 317 | + if (nrows.NE.ncols) then | |
| 318 | + write(*,*)'****** ERROR: nrows.NE.ncols ******' | |
| 319 | + end if | |
| 320 | +! write(*,*)'frequency=',freq,' n=',nrows | |
| 321 | + | |
| 322 | + if (loop.EQ.2) then | |
| 323 | + freq_in(n_freq_in)=freq | |
| 324 | + end if | |
| 325 | + | |
| 326 | + do r=1,nrows | |
| 327 | + | |
| 328 | + read(fh2_output_file_unit,'(A)',END=1000,ERR=1000)line | |
| 329 | + | |
| 330 | + if (loop.EQ.2) then | |
| 331 | + | |
| 332 | +! replace the 'j's by a space then read the complex data | |
| 333 | + local_line_length=len(trim(line)) | |
| 334 | + | |
| 335 | + do i=1,local_line_length | |
| 336 | + if (line(i:i).EQ.'j') line(i:i)=' ' | |
| 337 | + end do | |
| 338 | + | |
| 339 | + read(line,*)(values(i),i=1,2*ncols) | |
| 340 | + | |
| 341 | + do c=1,ncols | |
| 342 | + | |
| 343 | + re=values(c*2-1) | |
| 344 | + im=values(c*2) | |
| 345 | + | |
| 346 | + Zc_in(n_freq_in,r,c)=cmplx(re,im) | |
| 347 | + | |
| 348 | + end do ! next column | |
| 349 | + | |
| 350 | + end if | |
| 351 | + | |
| 352 | + end do ! next row | |
| 353 | + | |
| 354 | + GOTO 10 ! continue to read the file | |
| 355 | + | |
| 356 | +! Jump here when the file has been read | |
| 357 | + | |
| 358 | +1000 CONTINUE | |
| 359 | + | |
| 360 | + if (loop.Eq.1) then | |
| 361 | + if (verbose) write(*,*)'Number of frequencies=',n_freq_in | |
| 362 | + ALLOCATE( freq_in(n_freq_in) ) | |
| 363 | + ALLOCATE( Zc_in(n_freq_in,nrows,ncols) ) | |
| 364 | + ALLOCATE( values(2*ncols) ) | |
| 365 | + rewind(unit=fh2_output_file_unit) | |
| 366 | + end if | |
| 367 | + | |
| 368 | + end do ! next file read loop | |
| 369 | + | |
| 370 | + CLOSE(unit=fh2_output_file_unit) | |
| 371 | + | |
| 372 | +! Check dimensions | |
| 373 | + | |
| 374 | + if (nrows.NE.dim) then | |
| 375 | + write(*,*)'ERROR in frequency_domain_analysis_FH2: nrows.NE.dim' | |
| 376 | + write(*,*)'nrows from FH2 =',nrows,' dim=',dim | |
| 377 | + write(run_status,*)'ERROR in frequency_domain_analysis_FH2: dimension error:',dim,nrows | |
| 378 | + CALL write_program_status() | |
| 379 | + STOP 1 | |
| 380 | + end if | |
| 381 | + | |
| 382 | +! ************* LOOP OVER FREQUENCY *************** | |
| 383 | + | |
| 384 | +! Loop over the specified frequencies | |
| 385 | + do frequency_loop=1,n_freq_in | |
| 386 | + | |
| 387 | +! get the frequency and angular frequency values | |
| 388 | + f=freq_in(frequency_loop) | |
| 389 | + w=2d0*pi*f | |
| 390 | + | |
| 391 | +! Use the global domain based L and C matrices and the domain voltage and current | |
| 392 | +! domain transformation matrices to calculate the impedance [Z] and admittance [Y] matrices | |
| 393 | + do row=1,dim | |
| 394 | + do col=1,dim | |
| 395 | + | |
| 396 | +! Evaluate the cable impedance filter function | |
| 397 | + Z_domain(row,col)=Zc_in(frequency_loop,row,col) | |
| 398 | + | |
| 399 | +! Evaluate the cable admittance filter function | |
| 400 | + Y_domain(row,col)=evaluate_Sfilter_frequency_response(spice_bundle_model%bundle%global_Y%sfilter_mat(row,col),f) | |
| 401 | + | |
| 402 | + end do ! next col | |
| 403 | + end do ! next row | |
| 404 | + | |
| 405 | +! Contribution to the impedance matrices from the conductor based impedance models is zero here | |
| 406 | + | |
| 407 | + Z_domain_conductor_impedance_correction(1:dim,1:dim)=(0d0,0d0) | |
| 408 | + | |
| 409 | + if (verbose) write(*,*)'Add transfer impedance contributions' | |
| 410 | + | |
| 411 | +! add transfer impedance contributions *********** NOT SURE WHETHER WE NEED TO DO ANYTHING HERE ********* | |
| 412 | + | |
| 413 | +! loop over conductors looking for shields. Note include all conductors including the reference here | |
| 414 | + do conductor=1,dim+1 | |
| 415 | + | |
| 416 | + is_shield1=spice_bundle_model%bundle%terminal_conductor_is_shield_flag(conductor) | |
| 417 | + | |
| 418 | + if (is_shield1) then | |
| 419 | +! add transfer impedance contributions to inner and outer domain conductors | |
| 420 | + | |
| 421 | + inner_domain=spice_bundle_model%bundle%terminal_conductor_to_inner_domain(conductor) | |
| 422 | + outer_domain=spice_bundle_model%bundle%terminal_conductor_to_outer_domain(conductor) | |
| 423 | + | |
| 424 | + CALL evaluate_conductor_impedance_model(spice_bundle_model%bundle%conductor_impedance(conductor), & | |
| 425 | + f,Zint_c,Rdc_c,Zint_t,Rdc_t) | |
| 426 | + | |
| 427 | +! Check whether the shield is the reference conductor in the outer domain - the contributions | |
| 428 | +! are different if this is the case. | |
| 429 | + | |
| 430 | + n_conductors_outer_domain=spice_bundle_model%bundle%n_conductors(outer_domain) | |
| 431 | + shield_conductor_number_in_outer_domain=spice_bundle_model%bundle%terminal_conductor_to_local_domain_conductor(conductor) | |
| 432 | + | |
| 433 | +! number of conductors in a domain is spice_bundle_model%bundle%n_conductors(domain) | |
| 434 | + if (shield_conductor_number_in_outer_domain.NE.n_conductors_outer_domain) then | |
| 435 | + | |
| 436 | +! loop over all conductors | |
| 437 | + do row=1,dim | |
| 438 | + | |
| 439 | +! get the domain of row conductor | |
| 440 | + domain1=spice_bundle_model%bundle%terminal_conductor_to_outer_domain(row) | |
| 441 | + | |
| 442 | + if (domain1.EQ.inner_domain) then | |
| 443 | +! The row conductor is in the inner shield domain and so gets a transfer impedance contribution from the shield conductor | |
| 444 | + | |
| 445 | +! the shield couples these two domains so add the transfer impedance term - also include term to make the matrix symmetric | |
| 446 | + domain_conductor1=spice_bundle_model%bundle%terminal_conductor_to_global_domain_conductor(row) | |
| 447 | + | |
| 448 | + domain_conductor2=spice_bundle_model%bundle%terminal_conductor_to_global_domain_conductor(conductor) | |
| 449 | + Z_domain_conductor_impedance_correction(domain_conductor1,domain_conductor2)= & | |
| 450 | + Z_domain_conductor_impedance_correction(domain_conductor1,domain_conductor2) -Zint_t | |
| 451 | + Z_domain_conductor_impedance_correction(domain_conductor2,domain_conductor1)= & | |
| 452 | + Z_domain_conductor_impedance_correction(domain_conductor2,domain_conductor1) -Zint_t | |
| 453 | + | |
| 454 | + if (verbose) then | |
| 455 | + write(*,*)'Shield conductor',conductor,' inner domain',inner_domain,' outer domain',outer_domain | |
| 456 | + write(*,*)'row',row,' col',col,' row domain',domain1,' col domain',domain2 | |
| 457 | + write(*,*)'Contribution to Zt(',domain_conductor1,domain_conductor2,')' | |
| 458 | + write(*,*)'Contribution to Zt(',domain_conductor2,domain_conductor1,')' | |
| 459 | + write(*,*)'Zt conductor:',-Zint_t | |
| 460 | + end if ! verbose | |
| 461 | + | |
| 462 | + end if ! transfer impedance term required | |
| 463 | + | |
| 464 | + end do ! next row conductor | |
| 465 | + | |
| 466 | + else ! shield IS reference conductor in outer domain | |
| 467 | + | |
| 468 | +! loop over all conductors | |
| 469 | + do row=1,dim | |
| 470 | + | |
| 471 | +! get the domain of row conductor | |
| 472 | + domain1=spice_bundle_model%bundle%terminal_conductor_to_outer_domain(row) | |
| 473 | + | |
| 474 | + if (domain1.EQ.inner_domain) then | |
| 475 | +! The row conductor is in the inner shield domain and so gets a transfer impedance contribution from the shield conductor | |
| 476 | + | |
| 477 | +! the shield couples these two domains so add the transfer impedance term - also include term to make the matrix symmetric | |
| 478 | + domain_conductor1=spice_bundle_model%bundle%terminal_conductor_to_global_domain_conductor(row) | |
| 479 | + | |
| 480 | +! As the shield conductor is the reference we need to find all the conductors contributing to the shield current | |
| 481 | +! note that the contribution is then -ve of the normal transfer impedance contribution as the currents are in the | |
| 482 | +! opposite direction | |
| 483 | + | |
| 484 | + do col=1,dim | |
| 485 | + | |
| 486 | + domain2=spice_bundle_model%bundle%terminal_conductor_to_outer_domain(col) | |
| 487 | +! Check the domain of the col conductor. If it is an outer domain conductor of the shield then it contributes | |
| 488 | + | |
| 489 | + if (domain2.EQ.outer_domain) then | |
| 490 | + | |
| 491 | + domain_conductor2=spice_bundle_model%bundle%terminal_conductor_to_global_domain_conductor(col) | |
| 492 | + | |
| 493 | + Z_domain_conductor_impedance_correction(domain_conductor1,domain_conductor2)= & | |
| 494 | + Z_domain_conductor_impedance_correction(domain_conductor1,domain_conductor2) +Zint_t | |
| 495 | + Z_domain_conductor_impedance_correction(domain_conductor2,domain_conductor1)= & | |
| 496 | + Z_domain_conductor_impedance_correction(domain_conductor2,domain_conductor1) +Zint_t | |
| 497 | + | |
| 498 | + if (verbose) then | |
| 499 | + write(*,*)'Shield conductor',conductor,' inner domain',inner_domain,' outer domain',outer_domain | |
| 500 | + write(*,*)'row',row,' col',col,' row domain',domain1,' col domain',domain2 | |
| 501 | + write(*,*)'Contribution to Zt(',domain_conductor1,domain_conductor2,')' | |
| 502 | + write(*,*)'Contribution to Zt(',domain_conductor2,domain_conductor1,')' | |
| 503 | + write(*,*)'Zt conductor:',-Zint_t | |
| 504 | + end if ! verbose | |
| 505 | + | |
| 506 | + end if ! transfer impedance term required for this col conductor | |
| 507 | + | |
| 508 | + end do ! next condutor to check | |
| 509 | + | |
| 510 | + end if ! transfer impedance term required for this row conductor | |
| 511 | + | |
| 512 | + end do ! next row conductor | |
| 513 | + | |
| 514 | + end if ! shield is/ is not reference conductor in outer domain | |
| 515 | + | |
| 516 | + end if ! conductor is a shield | |
| 517 | + | |
| 518 | + end do ! next conductor | |
| 519 | + | |
| 520 | +! Add the conductor impedance contributions to the domain based impedance matrix | |
| 521 | + Z_domain(:,:)=Z_domain(:,:)+Z_domain_conductor_impedance_correction(:,:) | |
| 522 | + | |
| 523 | + if (verbose) then | |
| 524 | + | |
| 525 | + write(*,*)'[R_domain]=Re[Z_domain]' | |
| 526 | + do row=1,dim | |
| 527 | + write(*,8020)(real(Z_domain(row,col)),col=1,dim) | |
| 528 | + end do | |
| 529 | + | |
| 530 | + end if ! verbose | |
| 531 | + | |
| 532 | + if (verbose) then | |
| 533 | + | |
| 534 | + write(*,*)'Im[Z_domain]' | |
| 535 | + do row=1,dim | |
| 536 | + write(*,8010)(aimag(Z_domain(row,col)),col=1,dim) | |
| 537 | + end do | |
| 538 | + | |
| 539 | + write(*,*)'[R_domain]=Re[Z_domain]' | |
| 540 | + do row=1,dim | |
| 541 | + write(*,8020)(real(Z_domain(row,col)),col=1,dim) | |
| 542 | + end do | |
| 543 | + | |
| 544 | + write(*,*)'Im[Y_domain]' | |
| 545 | + do row=1,dim | |
| 546 | + write(*,8010)(aimag(Y_domain(row,col)),col=1,dim) | |
| 547 | + end do | |
| 548 | +8010 format(20ES10.2) | |
| 549 | +8020 format(20F12.4) | |
| 550 | + | |
| 551 | + end if ! verbose | |
| 552 | + | |
| 553 | +! Get the incident field amplitude | |
| 554 | + Einc=cmplx(spice_bundle_model%Eamplitude) | |
| 555 | + | |
| 556 | +! Solve the frequency domain multi-conductor transmission line equations with the specified termination circuit and | |
| 557 | +! incident field excitation, return the required conductor voltage in Vout. | |
| 558 | + if (.NOT.run_validation_test_Vbased) then | |
| 559 | + | |
| 560 | + CALL frequency_domain_MTL_solution(dim,Z_domain,Y_domain,MV,MVI,MI,MII, & | |
| 561 | + Einc,spice_bundle_model%Ex,spice_bundle_model%Ey,spice_bundle_model%Ez, & | |
| 562 | + spice_bundle_model%Hx,spice_bundle_model%Hy,spice_bundle_model%Hz, & | |
| 563 | + spice_bundle_model%kx,spice_bundle_model%ky,spice_bundle_model%kz, & | |
| 564 | + local_conductor_x_offset, & | |
| 565 | + local_conductor_y_offset, & | |
| 566 | + spice_bundle_model%bundle%ground_plane_present, & | |
| 567 | + spice_bundle_model%bundle%ground_plane_x, & | |
| 568 | + spice_bundle_model%bundle%ground_plane_y, & | |
| 569 | + spice_bundle_model%bundle%ground_plane_theta, & | |
| 570 | + spice_bundle_model%length,Vs1,Z1,Vs2,Z2, & | |
| 571 | + is_shielded_flag, & | |
| 572 | + f,spice_validation_test%output_end,spice_validation_test%output_conductor, & | |
| 573 | + spice_validation_test%output_conductor_ref,Vout) | |
| 574 | + | |
| 575 | + else | |
| 576 | + | |
| 577 | + CALL frequency_domain_MTL_solution_V(dim,Z_domain,Y_domain,MV,MVI,MI,MII, & | |
| 578 | + Einc,spice_bundle_model%Ex,spice_bundle_model%Ey,spice_bundle_model%Ez, & | |
| 579 | + spice_bundle_model%Hx,spice_bundle_model%Hy,spice_bundle_model%Hz, & | |
| 580 | + spice_bundle_model%kx,spice_bundle_model%ky,spice_bundle_model%kz, & | |
| 581 | + local_conductor_x_offset, & | |
| 582 | + local_conductor_y_offset, & | |
| 583 | + spice_bundle_model%bundle%ground_plane_present, & | |
| 584 | + spice_bundle_model%bundle%ground_plane_x, & | |
| 585 | + spice_bundle_model%bundle%ground_plane_y, & | |
| 586 | + spice_bundle_model%bundle%ground_plane_theta, & | |
| 587 | + spice_bundle_model%length,Vs1,Z1,Vs2,Z2, & | |
| 588 | + is_shielded_flag, & | |
| 589 | + f,spice_validation_test%output_end,spice_validation_test%output_conductor, & | |
| 590 | + spice_validation_test%output_conductor_ref,Vout) | |
| 591 | + | |
| 592 | + end if | |
| 593 | +! Output the result to file | |
| 594 | + | |
| 595 | + if (spice_validation_test%output_type.EQ.'li') then | |
| 596 | + | |
| 597 | + if (plot_real) then | |
| 598 | + write(analytic_soln_file_unit,*)f,real(Vout),aimag(Vout) | |
| 599 | + else | |
| 600 | + write(analytic_soln_file_unit,*)f,abs(Vout),atan2(aimag(Vout),real(Vout)) | |
| 601 | + end if | |
| 602 | + | |
| 603 | + else if (spice_validation_test%output_type.EQ.'dB') then | |
| 604 | + | |
| 605 | + write(analytic_soln_file_unit,*)f,20d0*log10(abs(Vout)) | |
| 606 | + | |
| 607 | + end if ! output format (linear or dB) | |
| 608 | + | |
| 609 | + end do ! next frequency in frequency loop | |
| 610 | + | |
| 611 | +! Close output file | |
| 612 | + Close(unit=analytic_soln_file_unit) | |
| 613 | + | |
| 614 | +! deallocate memory | |
| 615 | + DEALLOCATE( Z_domain ) | |
| 616 | + DEALLOCATE( Y_domain ) | |
| 617 | + | |
| 618 | + DEALLOCATE( Z_domain_conductor_impedance_correction ) | |
| 619 | + | |
| 620 | + DEALLOCATE( Vs1 ) | |
| 621 | + DEALLOCATE( Z1 ) | |
| 622 | + DEALLOCATE( Vs2 ) | |
| 623 | + DEALLOCATE( Z2 ) | |
| 624 | + | |
| 625 | +! domain transformation matrices | |
| 626 | + DEALLOCATE( MI ) | |
| 627 | + DEALLOCATE( MII ) | |
| 628 | + DEALLOCATE( MV ) | |
| 629 | + DEALLOCATE( MVI ) | |
| 630 | + | |
| 631 | + DEALLOCATE( is_shielded_flag ) | |
| 632 | + DEALLOCATE( local_conductor_x_offset ) | |
| 633 | + DEALLOCATE( local_conductor_y_offset ) | |
| 634 | + | |
| 635 | +! temporary working matrices | |
| 636 | + DEALLOCATE( TM1 ) | |
| 637 | + | |
| 638 | + DEALLOCATE( freq_in ) | |
| 639 | + DEALLOCATE( Zc_in ) | |
| 640 | + DEALLOCATE( values ) | |
| 641 | + | |
| 642 | + RETURN | |
| 643 | + | |
| 644 | +END SUBROUTINE frequency_domain_analysis_FH2 | ... | ... |
SRC/compare_results.F90
| ... | ... | @@ -51,6 +51,8 @@ |
| 51 | 51 | ! HISTORY |
| 52 | 52 | ! |
| 53 | 53 | ! started 24/11/2015 CJS |
| 54 | +! 26/10/2023 CJS don't send exit code 1 if there is an error. This allows results to be plotted using | |
| 55 | +! the generate_spice_cable_bundle_model process | |
| 54 | 56 | ! |
| 55 | 57 | ! _________________________________________________________________ |
| 56 | 58 | ! |
| ... | ... | @@ -432,7 +434,8 @@ IMPLICIT NONE |
| 432 | 434 | |
| 433 | 435 | run_status='ERROR: Sample not found in file 2' |
| 434 | 436 | CALL write_program_status() |
| 435 | - STOP 1 | |
| 437 | +! STOP 1 | |
| 438 | + GOTO 2000 | |
| 436 | 439 | |
| 437 | 440 | 1000 CONTINUE |
| 438 | 441 | |
| ... | ... | @@ -447,6 +450,8 @@ IMPLICIT NONE |
| 447 | 450 | local_compare_results_value=local_compare_results_value+ & |
| 448 | 451 | error*( ((dataset1%x(sample+1))-(dataset1%x(sample-1)) )/2d0) & |
| 449 | 452 | /( (dataset1%x(sample_max+1))-(dataset1%x(sample_min-1)) ) |
| 453 | + | |
| 454 | +2000 CONTINUE | |
| 450 | 455 | |
| 451 | 456 | end do ! next sample in the integration over x |
| 452 | 457 | ... | ... |
SRC/spice_cable_bundle_model_builder.F90
| ... | ... | @@ -571,6 +571,9 @@ integer :: i |
| 571 | 571 | if (INDEX(line,'no_high_freq_zt_model').NE.0) high_freq_Zt_model=.FALSE. |
| 572 | 572 | if (INDEX(line,'plot_real').NE.0) plot_real=.TRUE. |
| 573 | 573 | if (INDEX(line,'plot_mag').NE.0) plot_real=.FALSE. |
| 574 | + | |
| 575 | + if (INDEX(line,'no_fasthenry').NE.0) use_FastHenry=.FALSE. | |
| 576 | + if (INDEX(line,'use_fasthenry').NE.0) use_FastHenry=.TRUE. | |
| 574 | 577 | |
| 575 | 578 | if (INDEX(line,'use_analytic_i').NE.0) run_validation_test_Vbased=.FALSE. |
| 576 | 579 | if (INDEX(line,'use_analytic_v').NE.0) run_validation_test_Vbased=.TRUE. |
| ... | ... | @@ -667,10 +670,20 @@ integer :: i |
| 667 | 670 | |
| 668 | 671 | if (spice_validation_test%analysis_type.EQ.analysis_type_AC) then |
| 669 | 672 | |
| 670 | - if (verbose) write(*,*)'CALLING: frequency_domain_analysis' | |
| 671 | - CALL frequency_domain_analysis(spice_bundle_model,spice_validation_test) | |
| 672 | - if (verbose) write(*,*)'FINISHED: frequency_domain_analysis' | |
| 673 | - | |
| 673 | + if (use_FastHenry) then | |
| 674 | + | |
| 675 | + if (verbose) write(*,*)'CALLING: frequency_domain_analysis using FastHenry2 impedance matrices' | |
| 676 | + CALL frequency_domain_analysis_FH2(spice_bundle_model,spice_validation_test) | |
| 677 | + if (verbose) write(*,*)'FINISHED: frequency_domain_analysis using FastHenry2 impedance matrices' | |
| 678 | + | |
| 679 | + else | |
| 680 | + | |
| 681 | + if (verbose) write(*,*)'CALLING: frequency_domain_analysis' | |
| 682 | + CALL frequency_domain_analysis(spice_bundle_model,spice_validation_test) | |
| 683 | + if (verbose) write(*,*)'FINISHED: frequency_domain_analysis' | |
| 684 | + | |
| 685 | + end if | |
| 686 | + | |
| 674 | 687 | else |
| 675 | 688 | |
| 676 | 689 | if (verbose) write(*,*)'CALLING: time_domain_analysis' | ... | ... |
SRC/write_FH_input_file.F90
| ... | ... | @@ -16,6 +16,9 @@ real(dp) :: gp_t,gp_sigma,gp_rh,gp_ex1,gp_ey1,gp_ez1,gp_ex2,gp_ey2,gp_ez2 |
| 16 | 16 | real(dp) :: gp_skin_depth |
| 17 | 17 | integer :: gp_nhinc,gp_seg1,gp_seg2 |
| 18 | 18 | |
| 19 | +real(dp) :: gp_xmin,gp_xmax | |
| 20 | +real(dp) :: gp_xc,gp_yc,gp_w,gp_h | |
| 21 | + | |
| 19 | 22 | character(len=80),allocatable :: gp_node1 |
| 20 | 23 | character(len=80),allocatable :: gp_node2 |
| 21 | 24 | |
| ... | ... | @@ -35,6 +38,14 @@ TYPE::conductor_type |
| 35 | 38 | real(dp) :: yc |
| 36 | 39 | real(dp) :: width |
| 37 | 40 | real(dp) :: height |
| 41 | + | |
| 42 | + real(dp) :: rss | |
| 43 | + real(dp) :: rss_outer | |
| 44 | + real(dp) :: xcss(7) | |
| 45 | + real(dp) :: ycss(7) | |
| 46 | + real(dp) :: rot_angle | |
| 47 | + integer :: n_layers2ss | |
| 48 | + | |
| 38 | 49 | integer :: n_layers2 |
| 39 | 50 | integer :: tot_n_layers |
| 40 | 51 | |
| ... | ... | @@ -74,6 +85,7 @@ integer,parameter :: type_cyl=1 |
| 74 | 85 | integer,parameter :: type_rect=2 |
| 75 | 86 | integer,parameter :: type_annulus=3 |
| 76 | 87 | integer,parameter :: type_gnd=4 |
| 88 | +integer,parameter :: type_seven_strand=5 | |
| 77 | 89 | |
| 78 | 90 | integer,parameter :: mesh_type_layer=1 |
| 79 | 91 | integer,parameter :: mesh_type_grid=2 |
| ... | ... | @@ -121,6 +133,10 @@ character :: type_ch |
| 121 | 133 | integer :: tot_n_segments,tot_n_filaments |
| 122 | 134 | integer :: gp_n_segments,gp_n_filaments |
| 123 | 135 | |
| 136 | +integer :: i | |
| 137 | + | |
| 138 | +real(dp) :: xpt,ypt | |
| 139 | + | |
| 124 | 140 | real(dp),parameter :: pi=3.1415926535 |
| 125 | 141 | |
| 126 | 142 | ! START |
| ... | ... | @@ -235,7 +251,33 @@ INCLUDE "WRITE_FH2_IPFILE/get_grid_type.F90" |
| 235 | 251 | write(*,*)'Enter the cylindrical conductor discretisation, dl in metres' |
| 236 | 252 | line=line+1 |
| 237 | 253 | read(*,*,ERR=9000)conductor_data(conductor)%dl |
| 238 | - | |
| 254 | + | |
| 255 | + else if ( (type_ch.EQ.'s').OR.(type_ch.EQ.'S') ) then | |
| 256 | + conductor_data(conductor)%type=type_seven_strand | |
| 257 | + | |
| 258 | +! work out the grid type | |
| 259 | + | |
| 260 | +INCLUDE "WRITE_FH2_IPFILE/get_grid_type.F90" | |
| 261 | + | |
| 262 | + write(*,*)Conductor,conductor,' mesh type=',conductor_data(conductor)%mesh_type | |
| 263 | + | |
| 264 | + write(*,*)'Enter the seven strand conductor centre coordinates, xc yc in metres' | |
| 265 | + line=line+1 | |
| 266 | + read(*,*,ERR=9000)conductor_data(conductor)%xc,conductor_data(conductor)%yc | |
| 267 | + | |
| 268 | + write(*,*)'Enter the seven strand conductor equivalent radius, rc in metres' | |
| 269 | + line=line+1 | |
| 270 | + read(*,*,ERR=9000)conductor_data(conductor)%rc | |
| 271 | + | |
| 272 | + write(*,*)'Enter the seven strand conductor rotation angle in degrees' | |
| 273 | + line=line+1 | |
| 274 | + read(*,*,ERR=9000)conductor_data(conductor)%rot_angle | |
| 275 | + conductor_data(conductor)%rot_angle=conductor_data(conductor)%rot_angle*pi/180d0 | |
| 276 | + | |
| 277 | + write(*,*)'Enter the seven strand conductor discretisation, dl in metres' | |
| 278 | + line=line+1 | |
| 279 | + read(*,*,ERR=9000)conductor_data(conductor)%dl | |
| 280 | + | |
| 239 | 281 | else if ( (type_ch.EQ.'r').OR.(type_ch.EQ.'R') ) then |
| 240 | 282 | conductor_data(conductor)%type=type_rect |
| 241 | 283 | |
| ... | ... | @@ -376,6 +418,71 @@ INCLUDE "WRITE_FH2_IPFILE/create_grid.F90" |
| 376 | 418 | write(*,*)'Unknown grid type' |
| 377 | 419 | STOP 1 |
| 378 | 420 | end if |
| 421 | + | |
| 422 | + else if (conductor_data(conductor)%type.EQ.type_seven_strand) then | |
| 423 | + | |
| 424 | +! radius of each strand for the same conductor area | |
| 425 | + conductor_data(conductor)%rss=conductor_data(conductor)%rc/sqrt(7.0) | |
| 426 | +! maximum radius of the combined conductors | |
| 427 | + conductor_data(conductor)%rss_outer=conductor_data(conductor)%rss*3.0 | |
| 428 | + | |
| 429 | +! seven conductor centre coordinates | |
| 430 | +! central conductor | |
| 431 | + conductor_data(conductor)%xcss(1)=conductor_data(conductor)%xc | |
| 432 | + conductor_data(conductor)%ycss(1)=conductor_data(conductor)%yc | |
| 433 | + do i=1,6 | |
| 434 | + angle=real(i-1)*2.0*pi/6.0+conductor_data(conductor)%rot_angle | |
| 435 | + conductor_data(conductor)%xcss(i+1)=conductor_data(conductor)%xc+2d0*conductor_data(conductor)%rss*cos(angle) | |
| 436 | + conductor_data(conductor)%ycss(i+1)=conductor_data(conductor)%yc+2d0*conductor_data(conductor)%rss*sin(angle) | |
| 437 | + end do | |
| 438 | + | |
| 439 | + if (conductor_data(conductor)%mesh_type.EQ.mesh_type_layer) then | |
| 440 | + | |
| 441 | + conductor_data(conductor)%n_layers2ss=NINT(conductor_data(conductor)%rss/conductor_data(conductor)%dl) | |
| 442 | + conductor_data(conductor)%tot_n_layers=7*2*conductor_data(conductor)%n_layers2ss | |
| 443 | + | |
| 444 | + else if (conductor_data(conductor)%mesh_type.EQ.mesh_type_grid) then | |
| 445 | + | |
| 446 | +! allocate grid for the circular geometry | |
| 447 | + conductor_data(conductor)%grid_dim=conductor_data(conductor)%rss_outer | |
| 448 | + | |
| 449 | +INCLUDE "WRITE_FH2_IPFILE/create_grid.F90" | |
| 450 | + | |
| 451 | +! Loop over the grid and set segments within the conductor | |
| 452 | + | |
| 453 | + conductor_data(conductor)%tot_n_layers=0 | |
| 454 | + | |
| 455 | +! loop over 7 strands | |
| 456 | + do i=1,7 | |
| 457 | + | |
| 458 | +! loop over grid | |
| 459 | + do ix=nxmin,nxmax | |
| 460 | + do iy=nymin,nymax | |
| 461 | + | |
| 462 | +! calculate dpt, the distance to the centre of strand i | |
| 463 | + xpt=conductor_data(conductor)%dl*real(ix)- & | |
| 464 | + (conductor_data(conductor)%xcss(i)-conductor_data(conductor)%xcss(1)) | |
| 465 | + ypt=conductor_data(conductor)%dl*real(iy)- & | |
| 466 | + (conductor_data(conductor)%ycss(i)-conductor_data(conductor)%ycss(1)) | |
| 467 | + | |
| 468 | + dpt=sqrt(xpt**2+ypt*2) | |
| 469 | + | |
| 470 | + if ( dpt.LE.conductor_data(conductor)%rss ) then | |
| 471 | + conductor_data(conductor)%grid(ix,iy)=1 | |
| 472 | + conductor_data(conductor)%depth(ix,iy)=conductor_data(conductor)%rss-dpt | |
| 473 | + conductor_data(conductor)%tot_n_layers=conductor_data(conductor)%tot_n_layers+1 | |
| 474 | + end if | |
| 475 | + end do | |
| 476 | + end do | |
| 477 | + | |
| 478 | + conductor_data(conductor)%n_layers2=0 | |
| 479 | + | |
| 480 | + end do ! next strand | |
| 481 | + | |
| 482 | + else | |
| 483 | + write(*,*)'Unknown grid type' | |
| 484 | + STOP 1 | |
| 485 | + end if | |
| 379 | 486 | |
| 380 | 487 | else if (conductor_data(conductor)%type.EQ.type_annulus) then |
| 381 | 488 | |
| ... | ... | @@ -457,6 +564,17 @@ if (ground_plane) then |
| 457 | 564 | write(20,'(9A)')'+ ',trim(gp_node2),' (',trim(adjustl(x_string)), & |
| 458 | 565 | ',',trim(adjustl(y_string)), & |
| 459 | 566 | ',',trim(adjustl(z_string)),')' |
| 567 | + | |
| 568 | + gp_xmin=min(gp_x(1),gp_x(2),gp_x(3)) | |
| 569 | + gp_xmax=max(gp_x(1),gp_x(2),gp_x(3)) | |
| 570 | + gp_xc=(gp_xmin+gp_xmax)/2d0 | |
| 571 | + gp_yc=gp_y(1) | |
| 572 | + gp_w=(gp_xmax-gp_xmin) | |
| 573 | + gp_h=gp_t | |
| 574 | + | |
| 575 | + CALL plot_layer(gp_xc,gp_yc,gp_w,gp_h,1d0,0d0,10) | |
| 576 | + | |
| 577 | + CALL plot_grid(gp_xc,gp_yc,gp_w,gp_h,1d0,0d0,1d0,gp_rh,gp_seg1,gp_nhinc,12) | |
| 460 | 578 | |
| 461 | 579 | end if |
| 462 | 580 | |
| ... | ... | @@ -520,6 +638,44 @@ do conductor=1,n_conductors |
| 520 | 638 | INCLUDE "WRITE_FH2_IPFILE/set_segments_from_grid.F90" |
| 521 | 639 | |
| 522 | 640 | end if ! mesh_type_grid |
| 641 | + | |
| 642 | + else if (conductor_data(conductor)%type.EQ.type_seven_strand) then | |
| 643 | + | |
| 644 | + if (conductor_data(conductor)%mesh_type.EQ.mesh_type_layer) then | |
| 645 | + | |
| 646 | + layer_number=0 | |
| 647 | + | |
| 648 | +! loop over 7 strands | |
| 649 | + do i=1,7 | |
| 650 | + | |
| 651 | + do layer=-conductor_data(conductor)%n_layers2ss+1,conductor_data(conductor)%n_layers2ss | |
| 652 | + | |
| 653 | + layer_number=layer_number+1 | |
| 654 | + | |
| 655 | + ymin=conductor_data(conductor)%dl*real(layer) | |
| 656 | + ymax=conductor_data(conductor)%dl*real(layer-1) | |
| 657 | + y=(ymin+ymax)/2.0 | |
| 658 | + x=sqrt(conductor_data(conductor)%rss**2-y**2) | |
| 659 | + | |
| 660 | + conductor_data(conductor)%x(layer_number)=conductor_data(conductor)%xcss(i) | |
| 661 | + conductor_data(conductor)%y(layer_number)=conductor_data(conductor)%ycss(i)+y | |
| 662 | + conductor_data(conductor)%w(layer_number)=2.0*x | |
| 663 | + conductor_data(conductor)%h(layer_number)=conductor_data(conductor)%dl | |
| 664 | + conductor_data(conductor)%d(layer_number)=0.0 | |
| 665 | + conductor_data(conductor)%anwinc(layer_number)=conductor_data(conductor)%nwinc | |
| 666 | + conductor_data(conductor)%anhinc(layer_number)=conductor_data(conductor)%nwinc | |
| 667 | + | |
| 668 | + end do ! next layer | |
| 669 | + | |
| 670 | + end do ! next strand | |
| 671 | + | |
| 672 | + else if (conductor_data(conductor)%mesh_type.EQ.mesh_type_grid) then | |
| 673 | + | |
| 674 | +! Loop over the grid and set segments within the circular conductor | |
| 675 | + | |
| 676 | +INCLUDE "WRITE_FH2_IPFILE/set_segments_from_grid.F90" | |
| 677 | + | |
| 678 | + end if ! mesh_type_grid | |
| 523 | 679 | |
| 524 | 680 | else if (conductor_data(conductor)%type.EQ.type_rect) then |
| 525 | 681 | ... | ... |