!
! 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 spice_cable_bundle_module
! CONTAINSE
! SUBROUTINE deallocate_spice_cable_bundle
! SUBROUTINE deallocate_spice_validation_test
!
! NAME
! MODULE spice_cable_bundle_module
!
! DESCRIPTION
! Data structures and subroutines relating to the spice models of cable bundles
!
! COMMENTS
!
!
! HISTORY
! started 3/12/2015 CJS
!
MODULE spice_cable_bundle_module
USE type_specifications
USE cable_module
USE cable_bundle_module
USE frequency_spec
IMPLICIT NONE
! This structure contains the information for a spice cable bundle model
TYPE::spice_model_specification_type
character(len=line_length) :: version
character(len=line_length) :: spice_model_name
! bundle cross section information
type(bundle_specification_type) :: bundle
! cable bundle length (m)
real(dp) :: length
! Incident field excitation specification
real(dp) :: Eamplitude,ktheta,kphi,etheta,ephi
real(dp) :: Ex,Ey,Ez,Hx,Hy,Hz,kx,ky,kz
logical :: include_incident_field
! Transfer impedance model specification
integer :: n_transfer_impedances
integer,allocatable :: Zt_conductor(:)
integer,allocatable :: Zt_direction(:)
! filter function fitting information for the propagation correction filters
! model order
integer :: FIT_model_order
! frequency range specification for the propagation correction filter fitting processs
type(frequency_specification) :: prop_corr_fit_freq_spec
END TYPE spice_model_specification_type
! This structure contains the information for the Validation test problem specification
TYPE::spice_validation_test_type
! termination specification
real(dp),allocatable :: Vs_end1(:),R_end1(:) ! transmission line end 1 voltage sources and resistances
real(dp),allocatable :: Vs_end2(:),R_end2(:) ! transmission line end 2 voltage sources and resistances
! Analysis type specification (a.c. or transient)
integer :: analysis_type
! frequency domain analysis parameters:
! frequency range specification for a.c.analysis
type(frequency_specification) :: analysis_freq_spec
! transient analysis parameters
real(dp) :: timestep,runtime
real(dp) :: risetime,width
! output conductor number and end number for validation
integer :: output_end,output_conductor,output_conductor_ref
character(LEN=2) :: output_type
END TYPE spice_validation_test_type
SAVE
! parameters required for the validation test circuit
integer,parameter :: analysis_type_AC=1
integer,parameter :: analysis_type_TRANS=2
character(LEN=19),parameter :: log_freq_header='#LOG_FREQUENCY_DATA'
character(LEN=19),parameter :: lin_freq_header='#LIN_FREQUENCY_DATA'
character(LEN=17),parameter :: time_header= '#TIME_DOMAIN_DATA'
CONTAINS
! NAME
! SUBROUTINE deallocate_spice_cable_bundle
!
! DESCRIPTION
! deallocate spice_cable_bundle structure data
!
! COMMENTS
!
!
! HISTORY
! started 3/12/2015 CJS
!
SUBROUTINE deallocate_spice_cable_bundle(spice_cable_bundle_model)
USE type_specifications
USE general_module
USE cable_module
USE cable_bundle_module
IMPLICIT NONE
! variables passed to subroutine
type(spice_model_specification_type),intent(INOUT) :: spice_cable_bundle_model
! local variables
! START
write(*,*)'Deallocating spice cable bundle structure'
! first deallocate the cable_bundle structure
CALL deallocate_cable_bundle(spice_cable_bundle_model%bundle)
if (allocated(spice_cable_bundle_model%Zt_conductor)) DEALLOCATE( spice_cable_bundle_model%Zt_conductor )
if (allocated(spice_cable_bundle_model%Zt_direction)) DEALLOCATE( spice_cable_bundle_model%Zt_direction )
write(*,*)'Finished Deallocating spice cable bundle structure'
RETURN
END SUBROUTINE deallocate_spice_cable_bundle
!
! NAME
! SUBROUTINE deallocate_spice_validation_test
!
! DESCRIPTION
! deallocate spice_validation_test structure data
!
! COMMENTS
!
!
! HISTORY
! started 3/12/2015 CJS
! started 1/02/2016 CJS: STAGE_2 developments
! started 24/03/2016 CJS: STAGE_3 developments
!
SUBROUTINE deallocate_spice_validation_test(spice_validation_test)
USE type_specifications
USE general_module
USE cable_module
USE cable_bundle_module
IMPLICIT NONE
! variables passed to subroutine
type(spice_validation_test_type),intent(INOUT) :: spice_validation_test
! local variables
! START
! deallocate termination circuit voltage source and resistance data
if (ALLOCATED( spice_validation_test%Vs_end1)) DEALLOCATE( spice_validation_test%Vs_end1)
if (ALLOCATED( spice_validation_test%R_end1 )) DEALLOCATE( spice_validation_test%R_end1 )
if (ALLOCATED( spice_validation_test%Vs_end2)) DEALLOCATE( spice_validation_test%Vs_end2)
if (ALLOCATED( spice_validation_test%R_end2 )) DEALLOCATE( spice_validation_test%R_end2 )
RETURN
END SUBROUTINE deallocate_spice_validation_test
END MODULE spice_cable_bundle_module