! ! 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 coax_set_parameters ! SUBROUTINE coax_set_internal_domain_information ! SUBROUTINE coax_plot ! ! NAME ! coax_set_parameters ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! Set the overall parameters for a coax cable ! ! COMMENTS ! Set the dimension of the domain transformation matrices to include an external reference conductor for the cable ! ! HISTORY ! ! started 10/5/2016 CJS ! 16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions ! ! SUBROUTINE coax_set_parameters(cable) USE type_specifications IMPLICIT NONE ! variables passed to subroutine type(cable_specification_type),intent(INOUT) :: cable ! local variables ! START cable%cable_type=cable_geometry_type_coax cable%tot_n_conductors=2 cable%tot_n_domains=2 cable%n_external_conductors=1 cable%n_internal_conductors=1 cable%n_internal_domains=1 cable%n_parameters=6 cable%n_dielectric_filters=2 cable%n_transfer_impedance_models=1 END SUBROUTINE coax_set_parameters ! ! NAME ! coax_set_internal_domain_information ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! Set the overall parameters for a coax cable ! ! COMMENTS ! ! ! HISTORY ! ! started 10/5/2016 CJS ! 8/5/2017 CJS: Include references to Theory_Manual ! ! SUBROUTINE coax_set_internal_domain_information(cable) USE type_specifications USE constants USE filter_module USE general_module IMPLICIT NONE ! variables passed to subroutine type(cable_specification_type),intent(INOUT) :: cable ! local variables integer :: dim integer :: domain type(Sfilter) :: jw type(Sfilter) :: temp_filter real(dp) :: epsr ! variables for cable parameter checks logical :: cable_spec_error real(dp) :: rw real(dp) :: rs real(dp) :: rd real(dp) :: t real(dp) :: sigma_s real(dp) :: sigma_w type(Sfilter) :: epsr1,epsr2,ZT character(LEN=error_message_length) :: message ! START if (verbose) write(*,*)'CALLED: coax_set_internal_domain_information' ! Check the cable parameters rw=cable%parameters(1) rs=cable%parameters(2) rd=cable%parameters(3) sigma_w=cable%parameters(4) t=cable%parameters(5) sigma_s=cable%parameters(6) epsr1=cable%dielectric_filter(1) epsr2=cable%dielectric_filter(2) ZT=cable%transfer_impedance(1) cable_spec_error=.FALSE. ! assume no errors initially message='' CALL coax_with_dielectric_check(rw,rs,rd,cable_spec_error,cable%cable_name,message) CALL conductivity_check(sigma_w,cable_spec_error,cable%cable_name,message) CALL conductivity_check(sigma_s,cable_spec_error,cable%cable_name,message) CALL dielectric_check(epsr1,cable_spec_error,cable%cable_name,message) CALL dielectric_check(epsr2,cable_spec_error,cable%cable_name,message) CALL transfer_impedance_check(Zt,cable_spec_error,cable%cable_name,message) CALL surface_impedance_check(ZT,sigma_s,rs,t,cable_spec_error,cable%cable_name,message) if (cable_spec_error) then run_status='ERROR in cable_model_builder, error on parameters for cable:'//trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if ! Set the parameters for the single internal domain domain=1 cable%n_internal_conductors_in_domain(domain)=2 ! The number of modes in the internal domain is 1 dim=1 cable%L_domain(domain)%dim=dim ALLOCATE(cable%L_domain(domain)%mat(dim,dim)) cable%C_domain(domain)%dim=dim ALLOCATE(cable%C_domain(domain)%mat(dim,dim)) cable%Z_domain(domain)%dim=dim ALLOCATE(cable%Z_domain(domain)%sfilter_mat(dim,dim)) cable%Y_domain(domain)%dim=dim ALLOCATE(cable%Y_domain(domain)%sfilter_mat(dim,dim)) ! evaluate the high frequency limit of the inner dielectric filter function epsr=evaluate_Sfilter_high_frequency_limit(epsr1) if (verbose) write(*,*)'High frequency relative permittivity=',epsr cable%L_domain(domain)%mat(1,1)=(mu0/(2d0*pi))*log(rs/rw) ! Theory_Manual_Eqn 6.3 cable%C_domain(domain)%mat(1,1)=2d0*pi*eps0*epsr/log(rs/rw) ! Theory_Manual_Eqn 6.4 jw=jwA_filter(1d0) cable%Z_domain(domain)%sfilter_mat(1,1)=( (mu0/(2d0*pi))*log(rs/rw) )*jw temp_filter=jw*epsr1 cable%Y_domain(domain)%sfilter_mat(1,1)=( 2d0*pi*eps0/log(rs/rw) )*temp_filter ! Deallocate all filters CALL deallocate_Sfilter(temp_filter) CALL deallocate_Sfilter(jw) ! Set the domain decomposition matrices ! Theory_Manual_Eqn 6.5, 6.6 ! The dimension of the domain transformation matrices is 3 dim=3 cable%MI%dim=dim ALLOCATE(cable%MI%mat(dim,dim)) cable%MV%dim=dim ALLOCATE(cable%MV%mat(dim,dim)) cable%MI%mat(1,1)=1d0 cable%MI%mat(1,2)=0d0 cable%MI%mat(1,3)=0d0 cable%MI%mat(2,1)=1d0 cable%MI%mat(2,2)=1d0 cable%MI%mat(2,3)=0d0 cable%MI%mat(3,1)=1d0 cable%MI%mat(3,2)=1d0 cable%MI%mat(3,3)=1d0 cable%MV%mat(1,1)=1d0 cable%MV%mat(1,2)=-1d0 cable%MV%mat(1,3)=0d0 cable%MV%mat(2,1)=0d0 cable%MV%mat(2,2)=1d0 cable%MV%mat(2,3)=-1d0 cable%MV%mat(3,1)=0d0 cable%MV%mat(3,2)=0d0 cable%MV%mat(3,3)=1d0 ! Set the local reference conductor numbering ALLOCATE( cable%local_reference_conductor(2) ) cable%local_reference_conductor(1)=2 ! inner wire, reference is the shield conductor cable%local_reference_conductor(2)=0 ! external domain conductor, reference not known ! Set the local domain information: include a reference conductor in the count ALLOCATE( cable%local_domain_n_conductors(1:cable%tot_n_domains) ) cable%local_domain_n_conductors(1)=2 ! inner domain cable%local_domain_n_conductors(2)=2 ! external domain ! Set the external domain conductor and dielectric information ALLOCATE( cable%external_model(cable%n_external_conductors) ) CALL reset_external_conductor_model(cable%external_model(1)) cable%external_model(1)%conductor_type=circle cable%external_model(1)%conductor_radius=rs cable%external_model(1)%dielectric_radius=rd cable%external_model(1)%dielectric_epsr=epsr2 ! set the conductor impedance model for the inner conductor cable%conductor_impedance(1)%impedance_model_type=impedance_model_type_cylindrical_with_conductivity cable%conductor_impedance(1)%radius=rw cable%conductor_impedance(1)%conductivity=sigma_w ! set the impedance model for the shield conductor ! now done in the surface impedance model checks ! if ((t.EQ.0d0).AND.(sigma.NE.0d0)) then !! we need to calculate the thickness to be consistent with the transfer impedance at d.c. i.e. R_dc = ZT_dc ! Rdc=cable%transfer_impedance(1)%a%coeff(0)/cable%transfer_impedance(1)%b%coeff(0) ! t=1d0/(2d0*pi*rs*sigma*Rdc) ! end if cable%conductor_impedance(2)%impedance_model_type=impedance_model_type_cylindrical_shield cable%conductor_impedance(2)%radius=rs cable%conductor_impedance(2)%thickness=t cable%conductor_impedance(2)%conductivity=sigma_s cable%conductor_impedance(2)%ZT_filter=ZT CALL deallocate_Sfilter(epsr1) CALL deallocate_Sfilter(epsr2) CALL deallocate_Sfilter(ZT) ALLOCATE( cable%conductor_label(1:cable%tot_n_conductors) ) cable%conductor_label(1)='Cable name: '//trim(cable%cable_name)// & '. type: '//trim(cable%cable_type_string)//'. conductor 1 : Inner wire' cable%conductor_label(2)='Cable name: '//trim(cable%cable_name)// & '. type: '//trim(cable%cable_type_string)//'. conductor 2 : Shield' END SUBROUTINE coax_set_internal_domain_information ! ! NAME ! coax_plot ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! plot coaxial cable ! ! COMMENTS ! ! ! HISTORY ! ! started 10/5/2016 CJS ! ! SUBROUTINE coax_plot(cable,x_offset,y_offset,theta,xmin,xmax,ymin,ymax) USE type_specifications USE general_module IMPLICIT NONE ! variables passed to subroutine type(cable_specification_type),intent(IN) :: cable real(dp),intent(IN) :: x_offset,y_offset,theta real(dp),intent(INOUT) :: xmin,xmax,ymin,ymax ! local variables real(dp) :: x,y,r ! START ! plot inner conductor r=cable%parameters(1) ! wire radius x=x_offset y=y_offset CALL write_circle(x,y,r,conductor_geometry_file_unit,xmin,xmax,ymin,ymax) ! plot shield conductor r=cable%parameters(2) ! shield radius x=x_offset y=y_offset CALL write_circle(x,y,r,conductor_geometry_file_unit,xmin,xmax,ymin,ymax) ! plot circular dielectric r=cable%parameters(3) ! dielectric radius x=x_offset y=y_offset CALL write_circle(x,y,r,dielectric_geometry_file_unit,xmin,xmax,ymin,ymax) RETURN END SUBROUTINE coax_plot