write_delay_line.F90 4.64 KB
!
! 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 <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 write_delay_line
!
! NAME
!     write_delay_line
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     Write a delay line element to the spice subcircuit file
!     This will either be a simple delay line (T element) or LTRA transmission line
!     with zero resistance dependent on the use_LTRA flag
!
!     INPUTS REQUIRED
!     1. spice_model_name      ! component name
!     2. node_1_in             ! controlling node number 1
!     3. node_2_in             ! controlling node number 2
!     4. node_1_out            ! controlled node number 1
!     5. node_2_out            ! controlled node number 2
!     6. Z0                    ! characteristic impedance
!     7. delay                 ! transmission delay
!     8. length                ! transmission line length
!
!     OUTPUTS
!     1. components written to the spice subcircuit file
!     
!
! COMMENTS
!     
!     
!
! HISTORY
!
!     started 20/10/2017 Try out robustness of LTRA as opposed to T elements for Ngspice transient analysis
!     16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
!     
!
  SUBROUTINE write_delay_line(spice_model_name,node_1,node_2, &
                              node_3,node_4,Z0,TD,length)

USE type_specifications
USE general_module
USE filter_module

IMPLICIT NONE

! variables passed to the subroutine

character(LEN=spice_name_length),intent(IN) :: spice_model_name     ! component name

integer,intent(IN) :: node_1                  ! delay line node number 1
integer,intent(IN) :: node_2                  ! delay line node number 2
integer,intent(IN) :: node_3                  ! delay line node number 3
integer,intent(IN) :: node_4                  ! delay line node number 4

real(dp),intent(IN) :: Z0                        ! characteristic impedance
real(dp),intent(IN) :: TD                        ! delay
real(dp),intent(IN) :: length                    ! length

! local variables

real(dp) :: velocity
real(dp) :: L_local
real(dp) :: C_local

! START

if (.NOT.use_LTRA) then

! write the delay line (T type) element

  write(spice_model_file_unit,'(A30,4I6,A4,ES16.6,A4,ES16.6)')spice_model_name,  &
                                           node_1,node_2,node_3,node_4,        &
                                           ' Z0=',Z0,' TD=',TD

else
! use the LTRA transmission line model

  velocity=length/TD

  C_local=1.0/(Z0*velocity)
  L_local=Z0/velocity

! write the LTRA element
  if (spice_version.EQ.Pspice) then
  
    write(spice_model_file_unit,'(A30,4I6,A5,ES16.6)')spice_model_name,  &
                                           node_1,node_2,node_3,node_4,            &
                                           ' LEN=',length
    write(spice_model_file_unit,'(A10,ES16.6,A9,ES16.6)')'+ R=0.0 L=',L_local,' G=0.0 C=',C_local
  
  else   ! Ngspice or LTspice
  
    write(spice_model_file_unit,'(A32,4I6,A36)')'O_'//spice_model_name,      &
                                           node_1,node_2,node_3,node_4,    &
                                           ' LTRA_'//spice_model_name
                                           
! write the associated .model 

    write(spice_model_file_unit,'(A42,A15,ES16.6,A3,ES16.6,A5,ES16.6,A2)')'.MODEL LTRA_'//spice_model_name,  &
                                              ' LTRA( R=0.0 L=',L_local,' C=',C_local,' LEN=',length,' )'

  end if ! spice version

end if ! use_LTRA


END SUBROUTINE write_delay_line