!
! 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 cylindrical_set_parameters
! SUBROUTINE cylindrical_set_internal_domain_information
! SUBROUTINE cylindrical_plot
!
! NAME
! cylindrical_set_parameters
!
! AUTHORS
! Chris Smartt
!
! DESCRIPTION
! Set the overall parameters for a cylindrical cable
!
! COMMENTS
!
!
! HISTORY
!
! started 12/4/2016 CJS
! 16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
!
!
SUBROUTINE cylindrical_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_cylindrical
cable%tot_n_conductors=1
cable%tot_n_domains=1
cable%n_external_conductors=1
cable%n_internal_conductors=0
cable%n_internal_domains=0
cable%n_parameters=3
cable%n_dielectric_filters=1
cable%n_transfer_impedance_models=0
END SUBROUTINE cylindrical_set_parameters
!
! NAME
! cylindrical_set_internal_domain_information
!
! AUTHORS
! Chris Smartt
!
! DESCRIPTION
! Set the overall parameters for a cylindrical_with_dielectric cable
!
! COMMENTS
! Set the dimension of the domain transformation matrices to include an external reference conductor for the cable
!
!
! HISTORY
!
! started 13/4/2016 CJS
! Include additional data for Laplace solver 12/7/2016
! 8/5/2017 CJS: Include references to Theory_Manual
!
SUBROUTINE cylindrical_set_internal_domain_information(cable)
USE type_specifications
USE general_module
USE constants
IMPLICIT NONE
! variables passed to subroutine
type(cable_specification_type),intent(INOUT) :: cable
! local variables
integer :: dim
! variables for cable parameter checks
logical :: cable_spec_error
real(dp) :: r
real(dp) :: rd
real(dp) :: sigma
type(Sfilter) :: epsr
character(LEN=error_message_length) :: message
! START
! Check the cable parameters
r=cable%parameters(1)
rd=cable%parameters(2)
sigma=cable%parameters(3)
epsr=cable%dielectric_filter(1)
cable_spec_error=.FALSE. ! assume no errors initially
message=''
CALL cylindrical_with_dielectric_check(r,rd,cable_spec_error,cable%cable_name,message)
CALL dielectric_check(epsr,cable_spec_error,cable%cable_name,message)
CALL conductivity_check(sigma,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 domain decomposition matrices ! Theory_Manual_Eqn 6.1, 6.2
! The dimension of the domain transformation matrices is 2
dim=2
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(2,1)=1d0
cable%MI%mat(2,2)=1d0
cable%MV%mat(1,1)=1d0
cable%MV%mat(1,2)=-1d0
cable%MV%mat(2,1)=0d0
cable%MV%mat(2,2)=1d0
! Set the local reference conductor numbering
ALLOCATE( cable%local_reference_conductor(1) )
cable%local_reference_conductor(1)=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 ! 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=r
cable%external_model(1)%dielectric_radius=rd
cable%external_model(1)%dielectric_epsr=epsr
! set the conductor impedance model for the conductor
cable%conductor_impedance(1)%impedance_model_type=impedance_model_type_cylindrical_with_conductivity
cable%conductor_impedance(1)%radius=r
cable%conductor_impedance(1)%conductivity=sigma
CALL deallocate_Sfilter(epsr)
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 : wire'
END SUBROUTINE cylindrical_set_internal_domain_information
!
! NAME
! cylindrical_plot
!
! AUTHORS
! Chris Smartt
!
! DESCRIPTION
! plot cylindrical cable with dielectric
!
! COMMENTS
!
!
! HISTORY
!
! started 14/4/2016 CJS
!
!
SUBROUTINE cylindrical_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 circular 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 circular dielectric
r=cable%parameters(2) ! 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 cylindrical_plot