shielded_twisted_pair_cm_dm_parameter_calculation.F90 3.18 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 shielded_twisted_pair_cm_dm_parameter_calculation
!
! NAME
!     shielded_twisted_pair_cm_dm_parameter_calculation
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     from the L and C matrix elements of a shielded twisted pair, calculate the 
!     L and C matrix elements for the common mode- differential model model 
!     If the dielectric in the shield is homogeneous then the capacitance
!     terms are calculated from the inductance values and the relative permittivity of the dielectric.
!
! COMMENTS
!      
!
! HISTORY
!
!     started 2/11/2016 CJS 
!
!
SUBROUTINE shielded_twisted_pair_cm_dm_parameter_calculation(L11,L12,C11,C12,epsr,LC,LD,CC,CD,dielectric_is_homogeneous)

USE type_specifications
USE constants

IMPLICIT NONE

! variables passed to subroutine

! diagonal and off diagonal elements of inductance matrix for a shielded twisted pair
  real(dp),INTENT(IN)  :: L11,L12 
  
! diagonal and off diagonal elements of capacitance matrix for a shielded twisted pair - only used for homogeneous
! dielectric case when capacitance matrix can be calculated from the inverse of the inductance matrix
  real(dp),INTENT(IN)  :: C11,C12 
  
  real(dp),INTENT(IN)  :: epsr  ! relative permittivity for homogeneous dielectric case
  
  logical,INTENT(IN)   :: dielectric_is_homogeneous ! flag to indicate the homogeneous dielectric case
  
  real(dp),INTENT(OUT) :: LC,LD      ! common mode and differential mode inductance
  
  real(dp),INTENT(OUT) :: CC,CD      ! common mode and differential mode capacitance

! local variables

! START

  LD=2d0*(L11-L12)      ! Theory_Manual_Eqn 3.21
  
  LC=0.5d0*(L11+L12)    ! Theory_Manual_Eqn 3.21

  if (dielectric_is_homogeneous) then

    CD=eps0*mu0*epsr/LD
    
    CC=eps0*mu0*epsr/LC

  else

    CD=0.5d0*(C11-C12)  ! Theory_Manual_Eqn 3.22
    
    CC=2d0*(C11+C12)    ! Theory_Manual_Eqn 3.22

  end if

END SUBROUTINE shielded_twisted_pair_cm_dm_parameter_calculation