ground_plane.F90 5.7 KB
!
! This file is part of SACAMOS, State of the Art CAble MOdels in 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-2017 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 <http://www.gnu.org/licenses/>.
! 
! 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 <http://www.gnu.org/licenses/>.
! 
! The University of Nottingham can be contacted at: ggiemr@nottingham.ac.uk
!
! File Contents:
! SUBROUTINE ground_plane_set_parameters
! SUBROUTINE ground_plane_set_internal_domain_information
! SUBROUTINE ground_plane_plot
!
! NAME
!     ground_plane_set_parameters
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     Set the overall parameters for a ground_plane cable
!
! COMMENTS
!      
!
! HISTORY
!
!     started 12/4/2016 CJS 
!
!
SUBROUTINE ground_plane_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_ground_plane
  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=0
  cable%n_dielectric_filters=0
  cable%n_transfer_impedance_models=0
  
END SUBROUTINE ground_plane_set_parameters
!
! NAME
!     ground_plane_set_internal_domain_information
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     Set the overall parameters for a ground_plane 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 
!
!
SUBROUTINE ground_plane_set_internal_domain_information(cable)

USE type_specifications
USE constants

IMPLICIT NONE

! variables passed to subroutine

  type(cable_specification_type),intent(INOUT)    :: cable

! local variables

  integer :: dim

! START
    
! Set the domain decomposition matrices 
! The ground plane forms the reference conductor for the domain, the domain
! decomposition matrices are as for an overshield i.e. Theory_Manual_Eqn 6.15, 6.16

! 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 global domain conductor numbering  
  ALLOCATE( cable%global_domain_conductor(1) )
  cable%global_domain_conductor(1)=0              ! global domain conductor numbers not yet known
 
! Set the terminal conductor numbering  
  ALLOCATE( cable%terminal_conductor(1) )
  cable%terminal_conductor(1)=0              ! terminal conductor numbers not yet known
  
! 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_radius=-1d0     ! negative-for now. Need to indicate that it is 'special'

END SUBROUTINE ground_plane_set_internal_domain_information
!
! NAME
!     ground_plane_plot
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     plot ground plane
!
! COMMENTS
!      
!
! HISTORY
!
!     started 14/4/2016 CJS 
!
!
SUBROUTINE ground_plane_plot(cable,x_offset,y_offset,theta,length,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,length
  real(dp),intent(INOUT) ::  xmin,xmax,ymin,ymax

! local variables

  real(dp) :: x,y

! START

! write first point of ground plane
  x=x_offset-(length/2d0)*cos(theta)
  y=y_offset-(length/2d0)*sin(theta)
  write(conductor_geometry_file_unit,8000)x,y
  xmin=min(xmin,x)
  xmax=max(xmax,x)
  ymin=min(ymin,y)
  ymax=max(ymax,y)

! write middle point of ground plane
  x=x_offset
  y=y_offset
  write(conductor_geometry_file_unit,8000)x,y

! write final point of ground plane
  x=x_offset+(length/2d0)*cos(theta)
  y=y_offset+(length/2d0)*sin(theta)
  write(conductor_geometry_file_unit,8000)x,y
  xmin=min(xmin,x)
  xmax=max(xmax,x)
  ymin=min(ymin,y)
  ymax=max(ymax,y)
  
8000 format (4E14.6)
  
  write(conductor_geometry_file_unit,*)
  write(conductor_geometry_file_unit,*)

  RETURN
  
END SUBROUTINE ground_plane_plot