!
! 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:
! MODULE cable_module
! CONTAINS
! SUBROUTINE reset_external_conductor_model
! SUBROUTINE read_cable
! SUBROUTINE write_cable
! SUBROUTINE deallocate_cable
!
! The following subroutines are also contained in the module via include files:
!
! cable_checks.F90: SUBROUTINE gt_zero_check
! cable_checks.F90: SUBROUTINE cylindrical_check
! cable_checks.F90: SUBROUTINE cylindrical_with_dielectric_check
! cable_checks.F90: SUBROUTINE coax_with_dielectric_check
! cable_checks.F90: SUBROUTINE twisted_pair_check
! cable_checks.F90: SUBROUTINE shielded_twisted_pair_check
! cable_checks.F90: SUBROUTINE spacewire_check
! cable_checks.F90: SUBROUTINE rectangular_check
! cable_checks.F90: SUBROUTINE flex_cable_check
! cable_checks.F90: SUBROUTINE dielectric_check
! cable_checks.F90: SUBROUTINE not_FD_dielectric_check
! cable_checks.F90: SUBROUTINE transfer_impedance_check
! cable_checks.F90: SUBROUTINE conductivity_check
! cable_checks.F90: SUBROUTINE surface_impedance_check
!
! conductor_impedance_model.F90: SUBROUTINE read_conductor_impedance_model
! conductor_impedance_model.F90: SUBROUTINE write_conductor_impedance_model
! conductor_impedance_model.F90: SUBROUTINE evaluate_conductor_impedance_model
! conductor_impedance_model.F90: SUBROUTINE calculate_Rdc
! conductor_impedance_model.F90: SUBROUTINE calculate_internal_impedance
! conductor_impedance_model.F90: SUBROUTINE calculate_internal_impedance_shell
! conductor_impedance_model.F90: SUBROUTINE calculate_internal_impedance_rectangular
! conductor_impedance_model.F90: SUBROUTINE ber_bei
! conductor_impedance_model.F90: SUBROUTINE deallocate_conductor_impedance_model
!
! shielded_twisted_pair_cm_dm_parameter_calculation.F90: SUBROUTINE shielded_twisted_pair_cm_dm_parameter_calculation
!
! The following included subroutines relate to individual cable types:
!
! cylindrical.F90: SUBROUTINE cylindrical_set_parameters
! cylindrical.F90: SUBROUTINE cylindrical_set_internal_domain_information
! cylindrical.F90: SUBROUTINE cylindrical_plot
!
! coax.F90: SUBROUTINE coax_set_parameters
! coax.F90: SUBROUTINE coax_set_internal_domain_information
! coax.F90: SUBROUTINE coax_plot
!
! twisted_pair.F90: SUBROUTINE twisted_pair_set_parameters
! twisted_pair.F90: SUBROUTINE twisted_pair_set_internal_domain_information
! twisted_pair.F90: SUBROUTINE twisted_pair_plot
!
! shielded_twisted_pair.F90: SUBROUTINE shielded_twisted_pair_set_parameters
! shielded_twisted_pair.F90: SUBROUTINE shielded_twisted_pair_set_internal_domain_information
! shielded_twisted_pair.F90: SUBROUTINE shielded_twisted_pair_plot
!
! spacewire.F90: SUBROUTINE spacewire_set_parameters
! spacewire.F90: SUBROUTINE spacewire_set_internal_domain_information
! spacewire.F90: SUBROUTINE spacewire_plot
!
! twinax.F90: SUBROUTINE twinax_set_parameters
! twinax.F90: SUBROUTINE twinax_set_internal_domain_information
! twinax.F90: SUBROUTINE twinax_plot
!
! flex_cable.F90: SUBROUTINE flex_cable_set_parameters
! flex_cable.F90: SUBROUTINE flex_cable_set_internal_domain_information
! flex_cable.F90: SUBROUTINE flex_cable_plot
!
! ML_flex_cable.F90: SUBROUTINE ML_flex_cable_set_parameters
! ML_flex_cable.F90: SUBROUTINE ML_flex_cable_set_internal_domain_information
! ML_flex_cable.F90: SUBROUTINE ML_flex_cable_plot
!
! Dconnector.F90: SUBROUTINE Dconnector_set_parameters
! Dconnector.F90: SUBROUTINE Dconnector_set_internal_domain_information
! Dconnector.F90: SUBROUTINE Dconnector_plot
!
! overshield.F90: SUBROUTINE overshield_set_parameters
! overshield.F90: SUBROUTINE overshield_set_internal_domain_information
! overshield.F90: SUBROUTINE overshield_plot
!
! ground_plane.F90: SUBROUTINE ground_plane_set_parameters
! ground_plane.F90: SUBROUTINE ground_plane_set_internal_domain_information
! ground_plane.F90: SUBROUTINE ground_plane_plot
!
!
! NAME
! MODULE cable_module
!
! Data structures and subroutines relating to cables in general
! plus subroutines tailerd to individual cable types
!
! COMMENTS
!
!
! HISTORY
! started 25/11/2015 CJS
! Include multiple domain cables 21/03/2016 CJS
! Include general conductor impedance model 12/05/2016 CJS
! put the external condcutor model information into its own structure 6/10/2016 CJS
! 16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
! 16/3/2018 CJS Add ML_flex_cable
! 24/10/2023 CJS Add impedance_model_type_FH2
!
MODULE cable_module
USE type_specifications
USE filter_module
USE frequency_spec
USE general_module
IMPLICIT NONE
TYPE:: conductor_impedance_model
! This structure holds the data required to specify a conductor loss model
! parameters for the following conductor loss models are encompassed by this data:
! impedance_model_type_PEC
! impedance_model_type_cylindrical_with_conductivity
! impedance_model_type_filter
! impedance_model_type_cylidrical_shell_with_conductivity
! impedance_model_type_cylindrical_shield
! impedance_model_type_rectangular_with_conductivity
! impedance_model_type_FH2
integer :: impedance_model_type
real(dp) :: radius
real(dp) :: conductivity
real(dp) :: width
real(dp) :: height
real(dp) :: Rdc
real(dp) :: thickness
real(dp) :: Resistance_multiplication_factor ! this is required for the common mode loss in the differential mode/
! common mode domain decomposition model of twisted pairs
! filter function for impedance_model_type_filter
type(Sfilter) :: ZT_filter
! parameters for impedance_model_type_transfer_impedance_from_braid_parameters
END TYPE conductor_impedance_model
TYPE:: external_conductor_model
! This structure contains the information to specify the external conductor(s) of a
! cable. This is required for the calculation on the PUL parameters of the external domain
! of the cable.
integer :: conductor_type
real(dp) :: conductor_radius
real(dp) :: conductor_sigma
real(dp) :: conductor_width
real(dp) :: conductor_width2
real(dp) :: conductor_height
real(dp) :: conductor_ox
real(dp) :: conductor_oy
real(dp) :: dielectric_radius
real(dp) :: dielectric_width
real(dp) :: dielectric_height
real(dp) :: dielectric_ox
real(dp) :: dielectric_oy
type(Sfilter) :: dielectric_epsr
END TYPE external_conductor_model
TYPE::cable_specification_type
! This structure contains all the information relating to a cable including:
! PUL parameters of internal domains (frequency domain Y, Z matrices plus high frequency L and C matrices)
! The voltage and current domain transformation matrices
! domain based reference conductors for each conductor
! conductor impedance models
! external conductor models
character(LEN=line_length) :: version
character(LEN=line_length) :: cable_name
character(LEN=line_length) :: cable_type_string
integer :: cable_type
integer :: tot_n_conductors
integer :: tot_n_domains
integer :: n_external_conductors
integer :: n_internal_conductors
integer :: n_internal_domains
integer :: n_parameters
real(dp),allocatable :: parameters(:) ! parameters read from the .cable_spec file
! frequency dependent dielectric models read from the .cable_spec file
integer :: n_dielectric_filters
type(Sfilter),allocatable :: dielectric_filter(:)
! transfer impedance models read from the .cable_spec file
integer :: n_transfer_impedance_models
type(Sfilter),allocatable :: transfer_impedance(:)
! conductor numbering information
integer,allocatable :: local_reference_conductor(:)
integer,allocatable :: local_domain_n_conductors(:)
integer,allocatable :: global_domain_conductor(:)
integer,allocatable :: terminal_conductor(:)
! Domain transformation matrices
type(matrix) :: MI
type(matrix) :: MV
! internal domain based information
integer,allocatable :: local_domain(:)
integer,allocatable :: n_internal_conductors_in_domain(:)
! High frequency inductance and capacitance matrices for each internal domain
type(matrix),allocatable :: L_domain(:)
type(matrix),allocatable :: C_domain(:)
! Frequency dependent impedance and admittance matrices for each internal domain
type(Sfilter_matrix),allocatable :: Z_domain(:)
type(Sfilter_matrix),allocatable :: Y_domain(:)
! conductor impedance models for each conductor in the cable
type(conductor_impedance_model),allocatable :: conductor_impedance(:)
! external conductor information
type(external_conductor_model),allocatable :: external_model(:)
! Y matrix element function fitting information for frequency dependent dielectrics
! model order
integer :: Y_fit_model_order
! frequency range specification for the function fitting for frequency dependent dielectrics
type(frequency_specification) :: Y_fit_freq_spec
character(LEN=line_length),allocatable :: conductor_label(:)
END TYPE cable_specification_type
! These constant parameters identify cable types, conductor shapes and impedance model types
integer,parameter :: cable_geometry_type_cylindrical =1
integer,parameter :: cable_geometry_type_twisted_pair =2
integer,parameter :: cable_geometry_type_overshield =3
integer,parameter :: cable_geometry_type_coax =4
integer,parameter :: cable_geometry_type_shielded_twisted_pair =5
integer,parameter :: cable_geometry_type_spacewire =6
integer,parameter :: cable_geometry_type_twinax =7
integer,parameter :: cable_geometry_type_flex_cable =8
integer,parameter :: cable_geometry_type_Dconnector =9
integer,parameter :: cable_geometry_type_ground_plane =10
integer,parameter :: cable_geometry_type_ML_flex_cable =11
integer,parameter :: impedance_model_type_PEC =0
integer,parameter :: impedance_model_type_cylindrical_with_conductivity =1
integer,parameter :: impedance_model_type_filter =2
integer,parameter :: impedance_model_type_cylidrical_shell_with_conductivity =3
integer,parameter :: impedance_model_type_cylindrical_shield =4
integer,parameter :: impedance_model_type_rectangular_with_conductivity =5
integer,parameter :: impedance_model_type_FH2 =6
CONTAINS
! The following include files contain processes specific to individual cable types
include 'cylindrical.F90'
include 'coax.F90'
include 'twisted_pair.F90'
include 'shielded_twisted_pair.F90'
include 'spacewire.F90'
include 'twinax.F90'
include 'flex_cable.F90'
include 'ML_flex_cable.F90'
include 'Dconnector.F90'
include 'overshield.F90'
include 'ground_plane.F90'
! The following subroutines apply to all cable types
include 'cable_checks.F90'
include 'shielded_twisted_pair_cm_dm_parameter_calculation.F90'
! The following include file contains all processes related to the conductor impedance models
include 'conductor_impedance_model.F90'
! NAME
! SUBROUTINE reset_external_conductor_model
!
! reset data relating to a cables external conductor model
!
! COMMENTS
!
!
! HISTORY
! started 6/10/2016 CJS
!
SUBROUTINE reset_external_conductor_model(ext_model)
USE type_specifications
USE general_module
USE maths
USE filter_module
IMPLICIT NONE
! variables passed to subroutine
type(external_conductor_model),intent(OUT) :: ext_model
! local variables
! START
ext_model%conductor_type=0d0
ext_model%conductor_radius=0d0
ext_model%conductor_sigma=0d0
ext_model%conductor_width=0d0
ext_model%conductor_width2=0d0
ext_model%conductor_height=0d0
ext_model%conductor_ox=0d0
ext_model%conductor_oy=0d0
ext_model%dielectric_radius=0d0
ext_model%dielectric_width=0d0
ext_model%dielectric_height=0d0
ext_model%dielectric_ox=0d0
ext_model%dielectric_oy=0d0
ext_model%dielectric_epsr=1d0
END SUBROUTINE reset_external_conductor_model
! NAME
! SUBROUTINE read_cable(unit)
!
! read cable structure from a specified unit
!
! COMMENTS
!
!
! HISTORY
! started 2/12/2015 CJS
!
SUBROUTINE read_cable(cable,file_unit)
USE type_specifications
USE general_module
USE maths
USE filter_module
IMPLICIT NONE
! variables passed to subroutine
type(cable_specification_type),intent(INOUT) :: cable
integer,intent(IN) :: file_unit
! local variables
character(len=filename_length) :: filename
integer :: i,j,i2,j2
integer :: domain
integer :: dim
integer :: matrix_dimension
logical :: file_exists
character(len=line_length) :: line
! START
! check the existance of the cable file and open it for reading
filename=trim(MOD_cable_lib_dir)//trim(cable%cable_name)//cable_file_extn
inquire(file=trim(filename),exist=file_exists)
if (.NOT.file_exists) then
run_status='ERROR, Cannot find the required cable file:'//trim(filename)
CALL write_program_status()
STOP 1
end if
! open and read the file
OPEN(unit=cable_file_unit,file=trim(filename))
if (verbose) write(*,*)'Opened file:',trim(filename)
! STAGE_1 this reading process is specific to stage 1 and cylindrical conductors only
read(cable_file_unit,'(A)',ERR=9000)cable%version
read(cable_file_unit,'(A)',ERR=9000)cable%cable_type_string
read(cable_file_unit,*,ERR=9000)cable%cable_type
read(cable_file_unit,*,ERR=9000)cable%tot_n_conductors
read(cable_file_unit,*,ERR=9000)cable%n_external_conductors
read(cable_file_unit,*,ERR=9000)cable%tot_n_domains
read(cable_file_unit,*,ERR=9000)cable%n_internal_conductors
read(cable_file_unit,*,ERR=9000)cable%n_internal_domains
read(cable_file_unit,*,ERR=9000)cable%n_parameters
ALLOCATE( cable%parameters(1:cable%n_parameters) )
do i=1,cable%n_parameters
read(cable_file_unit,*,ERR=9000)cable%parameters(i)
end do
! read the frequency dependent dielectric information
read(cable_file_unit,*,ERR=9000)cable%n_dielectric_filters
if (cable%n_dielectric_filters.GT.0) then
ALLOCATE( cable%dielectric_filter(1:cable%n_dielectric_filters) )
do i=1,cable%n_dielectric_filters
read(cable_file_unit,*,ERR=9000) ! comment line
CALL read_Sfilter(cable%dielectric_filter(i),cable_file_unit)
end do
end if
! read the frequency dependent conductor impedance information
read(cable_file_unit,*,ERR=9000) ! comment line
ALLOCATE( cable%conductor_impedance(1:cable%tot_n_conductors) )
do i=1,cable%tot_n_conductors
CALL read_conductor_impedance_model(cable%conductor_impedance(i),cable_file_unit)
end do
read(file_unit,*) ! comment line
read(file_unit,*)matrix_dimension ! MI matrix dimension
cable%MI%dim=matrix_dimension
ALLOCATE( cable%MI%mat(1:matrix_dimension,1:matrix_dimension) )
CALL dread_matrix(cable%MI%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
read(file_unit,*) ! comment line
read(file_unit,*)matrix_dimension ! MV matrix dimension
cable%MV%dim=matrix_dimension
ALLOCATE( cable%MV%mat(1:matrix_dimension,1:matrix_dimension) )
CALL dread_matrix(cable%MV%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
! write the internal impedance and admittance matrices here
if ((cable%n_internal_domains).GT.0) then
! allocate internal domain information
ALLOCATE(cable%n_internal_conductors_in_domain(1:cable%n_internal_domains))
ALLOCATE(cable%L_domain(1:cable%n_internal_domains))
ALLOCATE(cable%C_domain(1:cable%n_internal_domains))
ALLOCATE(cable%Z_domain(1:cable%n_internal_domains))
ALLOCATE(cable%Y_domain(1:cable%n_internal_domains))
do domain=1,cable%n_internal_domains
read(file_unit,*) ! comment line (domain number)
read(file_unit,*)cable%n_internal_conductors_in_domain(domain)
read(file_unit,*) ! comment line
read(file_unit,*)matrix_dimension ! L matrix dimension
cable%L_domain(domain)%dim=matrix_dimension
ALLOCATE( cable%L_domain(domain)%mat(1:matrix_dimension,1:matrix_dimension) )
CALL dread_matrix(cable%L_domain(domain)%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
read(file_unit,*) ! comment line
read(file_unit,*)matrix_dimension ! C matrix dimension
cable%C_domain(domain)%dim=matrix_dimension
ALLOCATE( cable%C_domain(domain)%mat(1:matrix_dimension,1:matrix_dimension) )
CALL dread_matrix(cable%C_domain(domain)%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
read(file_unit,*) ! comment line
CALL read_Sfilter_matrix( cable%Z_domain(domain),file_unit )
read(file_unit,*) ! comment line
CALL read_Sfilter_matrix( cable%Y_domain(domain),file_unit )
end do ! next domain
end if ! there are internal domains
! read the local reference conductor information
ALLOCATE( cable%local_reference_conductor(1:cable%tot_n_conductors) )
read(file_unit,*)! comment line
do i=1,cable%tot_n_conductors
read(file_unit,*)cable%local_reference_conductor(i)
end do
! read the local domain information
read(file_unit,*)! comment line
ALLOCATE( cable%local_domain_n_conductors(1:cable%tot_n_domains) )
do i=1,cable%tot_n_domains
read(file_unit,*)cable%local_domain_n_conductors(i)
end do
read(file_unit,*)! comment line
ALLOCATE( cable%external_model(1:cable%n_external_conductors) )
do i=1,cable%n_external_conductors
read(file_unit,*) cable%external_model(i)%conductor_type
read(file_unit,*) cable%external_model(i)%conductor_radius
read(file_unit,*) cable%external_model(i)%conductor_sigma
read(file_unit,*) cable%external_model(i)%conductor_width
read(file_unit,*) cable%external_model(i)%conductor_width2
read(file_unit,*) cable%external_model(i)%conductor_height
! format change. This way of reading allows backward compatibility
read(file_unit,'(A)')line
read(line,*,err=100) cable%external_model(i)%conductor_ox,cable%external_model(i)%conductor_oy
GOTO 110
100 read(line,*) cable%external_model(i)%conductor_ox
cable%external_model(i)%conductor_oy=0d0
110 CONTINUE
read(file_unit,*) cable%external_model(i)%dielectric_radius
read(file_unit,*) cable%external_model(i)%dielectric_width
read(file_unit,*) cable%external_model(i)%dielectric_height
! format change. This way of reading allows backward compatibility
read(file_unit,'(A)')line
read(line,*,err=200) cable%external_model(i)%dielectric_ox,cable%external_model(i)%dielectric_oy
GOTO 210
200 read(line,*) cable%external_model(i)%dielectric_ox
cable%external_model(i)%dielectric_oy=0d0
210 CONTINUE
CALL read_Sfilter(cable%external_model(i)%dielectric_epsr,cable_file_unit)
end do
! read the conductor labels
ALLOCATE( cable%conductor_label(1:cable%tot_n_conductors) )
read(file_unit,*) ! comment line
do i=1,cable%tot_n_conductors
read(file_unit,'(A)')cable%conductor_label(i)
end do
! Allocate the global domain conductor and termainal conductor information and set to zero as this is
! not known at the cable building stage
ALLOCATE( cable%global_domain_conductor(1:cable%tot_n_conductors) )
cable%global_domain_conductor(1:cable%tot_n_conductors)=0
ALLOCATE( cable%terminal_conductor(1:cable%tot_n_conductors) )
cable%terminal_conductor(1:cable%tot_n_conductors)=0
CLOSE(unit=cable_file_unit)
if (verbose) write(*,*)'Closed file:',trim(filename)
RETURN
9000 run_status='ERROR reading the cable file:'//trim(filename)
CALL write_program_status()
STOP 1
END SUBROUTINE read_cable
! NAME
! SUBROUTINE write_cable
!
! write cable structure to a specified unit
!
! COMMENTS
!
!
! HISTORY
! started 2/12/2015 CJS
!
SUBROUTINE write_cable(cable,file_unit)
USE type_specifications
USE general_module
USE maths
USE filter_module
IMPLICIT NONE
! variables passed to subroutine
type(cable_specification_type),intent(IN) :: cable
integer,intent(IN) :: file_unit
! local variables
character(len=filename_length) :: filename
integer :: i,j
integer :: domain
integer :: matrix_dimension
! START
! open the output (.cable) file
filename=trim(MOD_cable_lib_dir)//trim(cable%cable_name)//cable_file_extn
if (verbose) write(*,'(A)')'Opening file:',trim(filename)
open(unit=file_unit,file=trim(filename))
! write .cable file
write(file_unit,'(A)')trim(cable%version)
write(file_unit,'(A)')trim(cable%cable_type_string)
write(file_unit,*)cable%cable_type,' # cable type number'
write(file_unit,*)cable%tot_n_conductors, ' # Total Number of conductors'
write(file_unit,*)cable%n_external_conductors,' # Number of external conductors'
write(file_unit,*)cable%tot_n_domains, ' # Total number of domains (including external domain)'
write(file_unit,*)cable%n_internal_conductors,' # Number of internal conductors'
write(file_unit,*)cable%n_internal_domains, ' # Number of internal domains'
! Number of external conductor parameters
write(file_unit,*)cable%n_parameters,' # Number of cable parameters'
do i=1,cable%n_parameters
write(file_unit,*)cable%parameters(i)
end do
! write the frequency dependent dielectric models
write(cable_file_unit,*)cable%n_dielectric_filters,' # number of frequency dependent dielectric models'
do i=1,cable%n_dielectric_filters
write(cable_file_unit,*)'# Dielectric filter number',i
CALL write_Sfilter(cable%dielectric_filter(i),cable_file_unit)
end do
! write the frequency dependent conductor impedance models
write(cable_file_unit,*)'# Conductor impedance models'
do i=1,cable%tot_n_conductors
CALL write_conductor_impedance_model(cable%conductor_impedance(i),cable_file_unit)
end do
! write the current and voltage local to global transformation matrices
matrix_dimension=cable%MI%dim
write(file_unit,*)'External to domain conductor current transformation matrix, MI'
write(file_unit,*)matrix_dimension,' Dimension of MI'
CALL dwrite_matrix(cable%MI%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
matrix_dimension=cable%MV%dim
write(file_unit,*)'External to domain conductor voltage transformation matrix, MV'
write(file_unit,*)matrix_dimension,' Dimension of MV'
CALL dwrite_matrix(cable%MV%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
if ((cable%n_internal_domains).GT.0) then
do domain=1,cable%n_internal_domains
write(file_unit,*)'Domain number',domain
write(file_unit,*)cable%n_internal_conductors_in_domain(domain),' # number of conductors'
! write the internal impedance and admittance matrices here
matrix_dimension=cable%L_domain(domain)%dim
write(file_unit,*)'High frequency Per-Unit-length Inductance Matrix, L'
write(file_unit,*)matrix_dimension,' Dimension of L'
CALL dwrite_matrix(cable%L_domain(domain)%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
matrix_dimension=cable%C_domain(domain)%dim
write(file_unit,*)'High frequency Per-Unit-length Capacitance Matrix, C'
write(file_unit,*)matrix_dimension,' Dimension of C'
CALL dwrite_matrix(cable%C_domain(domain)%mat,matrix_dimension,matrix_dimension,matrix_dimension,file_unit)
write(file_unit,*)'Per-Unit-length Impedance Matrix, Z'
CALL write_Sfilter_matrix( cable%Z_domain(domain),file_unit )
write(file_unit,*)'Per-Unit-length Admittance Matrix, Y'
CALL write_Sfilter_matrix( cable%Y_domain(domain),file_unit )
end do ! next domain
end if ! there are internal domains
! write the local reference conductor information
write(file_unit,*)' # Local reference conductor for internal domains'
do i=1,cable%tot_n_conductors
write(file_unit,*)cable%local_reference_conductor(i)
end do
! Write the local domain information
write(file_unit,*)' # number of conductors in each domain'
do i=1,cable%tot_n_domains
write(file_unit,*)cable%local_domain_n_conductors(i)
end do
write(file_unit,*)' # External conductor information and dielectric model'
do i=1,cable%n_external_conductors
write(file_unit,*) cable%external_model(i)%conductor_type,' conductor type'
write(file_unit,*) cable%external_model(i)%conductor_radius ,' conductor_radius '
write(file_unit,*) cable%external_model(i)%conductor_sigma ,' conductor_sigma '
write(file_unit,*) cable%external_model(i)%conductor_width ,' conductor_width '
write(file_unit,*) cable%external_model(i)%conductor_width2 ,' conductor_width2 '
write(file_unit,*) cable%external_model(i)%conductor_height ,' conductor_height '
write(file_unit,*) cable%external_model(i)%conductor_ox,cable%external_model(i)%conductor_oy &
,' conductor_ox, conductor_oy '
write(file_unit,*) cable%external_model(i)%dielectric_radius ,' dielectric_radius'
write(file_unit,*) cable%external_model(i)%dielectric_width ,' dielectric_width '
write(file_unit,*) cable%external_model(i)%dielectric_height ,' dielectric_height'
write(file_unit,*) cable%external_model(i)%dielectric_ox,cable%external_model(i)%dielectric_oy &
,' dielectric_ox, dielectric_oy '
CALL write_Sfilter(cable%external_model(i)%dielectric_epsr,cable_file_unit)
end do
! write the conductor labels
write(file_unit,*)' # Conductor labels'
do i=1,cable%tot_n_conductors
write(file_unit,*)trim(cable%conductor_label(i))
end do
! close .cable file
CLOSE(unit=file_unit)
RETURN
END SUBROUTINE write_cable
! NAME
! SUBROUTINE deallocate_cable
!
! deallocate cable structure data
!
! COMMENTS
!
!
! HISTORY
! started 2/12/2015 CJS
!
SUBROUTINE deallocate_cable(cable)
USE type_specifications
USE general_module
USE filter_module
IMPLICIT NONE
! variables passed to subroutine
type(cable_specification_type),intent(INOUT) :: cable
! local variables
integer :: domain
integer :: parameter
integer :: i
! START
if ( allocated(cable%parameters) ) DEALLOCATE( cable%parameters )
if (ALLOCATED(cable%n_internal_conductors_in_domain)) then
DEALLOCATE(cable%n_internal_conductors_in_domain)
end if
if (ALLOCATED(cable%L_domain)) then
do domain=1,cable%n_internal_domains
DEALLOCATE(cable%L_domain(domain)%mat)
end do
DEALLOCATE(cable%L_domain)
end if
if (ALLOCATED(cable%C_domain)) then
do domain=1,cable%n_internal_domains
DEALLOCATE(cable%C_domain(domain)%mat)
end do
DEALLOCATE(cable%C_domain)
end if
if (ALLOCATED(cable%Z_domain)) then
do domain=1,cable%n_internal_domains
CALL deallocate_Sfilter_matrix( cable%Z_domain(domain) )
end do
DEALLOCATE(cable%Z_domain)
end if
if (ALLOCATED(cable%Y_domain)) then
do domain=1,cable%n_internal_domains
CALL deallocate_Sfilter_matrix( cable%Y_domain(domain) )
end do
DEALLOCATE(cable%Y_domain)
end if
if (ALLOCATED(cable%MI%mat)) then
DEALLOCATE(cable%MI%mat)
end if
if (ALLOCATED(cable%MV%mat)) then
DEALLOCATE(cable%MV%mat)
end if
if (ALLOCATED(cable%local_reference_conductor)) then
DEALLOCATE(cable%local_reference_conductor)
end if
if (ALLOCATED(cable%global_domain_conductor)) then
DEALLOCATE(cable%global_domain_conductor)
end if
if (ALLOCATED(cable%terminal_conductor)) then
DEALLOCATE(cable%terminal_conductor)
end if
if (ALLOCATED(cable%local_domain_n_conductors)) then
DEALLOCATE(cable%local_domain_n_conductors)
end if
if ( ALLOCATED(cable%external_model) ) then
do i=1,cable%n_external_conductors
CALL deallocate_Sfilter(cable%external_model(i)%dielectric_epsr)
end do
DEALLOCATE ( cable%external_model )
end if
if (ALLOCATED( cable%dielectric_filter) ) then
do i=1,cable%n_dielectric_filters
CALL deallocate_Sfilter(cable%dielectric_filter(i))
end do
DEALLOCATE(cable%dielectric_filter)
end if
if (ALLOCATED( cable%transfer_impedance) ) then
do i=1,cable%n_transfer_impedance_models
CALL deallocate_Sfilter(cable%transfer_impedance(i))
end do
DEALLOCATE(cable%transfer_impedance)
end if
if (ALLOCATED( cable%conductor_impedance) ) then
do i=1,cable%tot_n_conductors
CALL deallocate_conductor_impedance_model(cable%conductor_impedance(i))
end do
DEALLOCATE(cable%conductor_impedance)
end if
if (ALLOCATED( cable%conductor_label )) then
DEALLOCATE(cable%conductor_label)
end if
RETURN
END SUBROUTINE deallocate_cable
END MODULE cable_module