!
! 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 create_spice_subcircuit_symbol_NGspice
! SUBROUTINE create_spice_subcircuit_symbol_LTspice
!
! NAME
!     create_spice_subcircuit_symbol_NGspice
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     This subroutine creates a symbol for the Spice subcircuit model for the cable bundle
!     to be used in schematic capture software
!
!     The file formats for Gschem can be found here: http://wiki.geda-project.org/geda:file_format_spec
!     
! COMMENTS
!     
!
! HISTORY
!
!     started 15/12/2015 CJS: STAGE_1 developments
!     2/8/2017 CJS: change filename path for the library file to be 
!     something that must be edited by the user/ GUI software
!     16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions
!
!
SUBROUTINE create_spice_subcircuit_symbol_NGspice(spice_bundle_model)

USE type_specifications
USE general_module
USE constants
USE cable_module
USE cable_bundle_module
USE spice_cable_bundle_module
USE circuit_symbol_module

IMPLICIT NONE

! variables passed to the subroutine

TYPE(spice_model_specification_type),intent(IN) :: spice_bundle_model

! local variables

character(len=filename_length)    :: filename                    ! filename for the symbol file
character(len=filename_length)    :: spice_subcircuit_filename   ! filename for the associated spice sub-circuit model

integer :: n_conductors

integer :: ymax_symbol    ! maximum y extent of the symbol (depends on the number of conductors)

integer :: xpin1(2),xpin2(2)  ! pin x coordinates for ends 1 and 2 of the transmission line symbol
integer :: ypin               ! pin y coordinate

integer :: xpin_label(2)      ! x coordinate for conductor labels at ends 1 and 2 of the transmission line symbol
integer :: align_label(2)     ! alignment type for symbols

! loop variables
integer :: pin                ! pin number
integer :: end                ! end number
integer :: conductor          ! conductor number

! temporary strings
character(len=line_length)    :: string1
character(len=line_length)    :: string2

! pin label strings
character(len=line_length)    :: pinnumber_string
character(len=line_length)    :: pinseq_string
character(len=line_length)    :: pinlabel_string

! START
  
! filename for the symbol. The directory for the symbol is read from the 
! .spice_model_spec file (i.e. specified by the GUI)

  filename=trim(spice_symbol_dir)//trim(spice_bundle_model%spice_model_name)//symbol_file_extn

! open the symbol file
  
  OPEN(unit=symbol_file_unit,file=filename)

  if (verbose) write(*,*)'Opened file:',trim(filename)

! calculate the size of the symbol from the number of conductors and set all symbol dimensions

  n_conductors=spice_bundle_model%bundle%tot_n_conductors

  ymax_symbol=ymin_offset+(n_conductors-1)*y_conductor_spacing+ymax_offset

! add a space for the incident field nodes  
  if (spice_bundle_model%include_incident_field) then
    ymax_symbol=ymax_symbol+y_conductor_spacing
  end if

! end 1 pin parameters # this could maybe go with parameters in the module...
  xpin1(1)=xmin_symbol-x_pin_length
  xpin2(1)=xmin_symbol
  
! end 2 pin parameters
  xpin1(2)=xmax_symbol+x_pin_length
  xpin2(2)=xmax_symbol
  
 ! write the header
  write(symbol_file_unit,'(A)')symbol_version

! write the rectangular box
  write(symbol_file_unit,'(A,4I6,A)')'L ',xmin_symbol,ymin_symbol,xmin_symbol,ymax_symbol,' 3 0 0 0 -1 -1'
  write(symbol_file_unit,'(A,4I6,A)')'L ',xmin_symbol,ymax_symbol,xmax_symbol,ymax_symbol,' 3 0 0 0 -1 -1'
  write(symbol_file_unit,'(A,4I6,A)')'L ',xmax_symbol,ymax_symbol,xmax_symbol,ymin_symbol,' 3 0 0 0 -1 -1'
  write(symbol_file_unit,'(A,4I6,A)')'L ',xmax_symbol,ymin_symbol,xmin_symbol,ymin_symbol,' 3 0 0 0 -1 -1'

! write the connection pins  
  xpin_label(1)=xmin_symbol
  xpin_label(2)=xmax_symbol
  align_label(1)=1   ! left
  align_label(2)=7   ! right
  
  pin=0
  do end=1,2
  
    do conductor=1,n_conductors
    
      pin=pin+1
      ypin=ymax_symbol-ymax_offset-(conductor-1)*y_conductor_spacing
      
      string1='pinnumber='
      CALL add_integer_to_string(string1,pin,pinnumber_string)
      
      string1='pinseq='
      CALL add_integer_to_string(string1,pin,pinseq_string)

      string1='pinlabel=c'      
      CALL add_integer_to_string(string1,conductor,string2)
      string1=trim(string2)//'_e'
      CALL add_integer_to_string(string1,end,pinlabel_string)
      
      write(symbol_file_unit,'(A,4I6,A)')'P ',xpin1(end),ypin,xpin2(end),ypin,' 1 0 0'
      write(symbol_file_unit,'(A)')'{'
      write(symbol_file_unit,'(A)')'T 150 250   5 8 0 0 0 6 1'
      write(symbol_file_unit,'(A)')trim(pinnumber_string)
      write(symbol_file_unit,'(A)')'T 150 150   5 8 0 0 0 8 1'
      write(symbol_file_unit,'(A)')trim(pinseq_string)
      write(symbol_file_unit,'(A,2I6,A,I3,A)')'T ',xpin_label(end),ypin,' 9 6 1 1 0 ',align_label(end),' 1'
      write(symbol_file_unit,'(A)')trim(pinlabel_string)
      write(symbol_file_unit,'(A)')'T 200 200   5 8 0 0 0 2 1'
      write(symbol_file_unit,'(A)')'pintype=pas'
      write(symbol_file_unit,'(A)')'}'
    
    end do ! next conductor
    
  end do ! other cable end

! add a space for the incident field nodes  
  if (spice_bundle_model%include_incident_field) then
    
! put the first Einc pin on the LHS of the symbol    
      end=1
      pin=pin+1
      ypin=ymax_symbol-ymax_offset-(n_conductors)*y_conductor_spacing
      
      string1='pinnumber='
      CALL add_integer_to_string(string1,pin,pinnumber_string)
      
      string1='pinseq='
      CALL add_integer_to_string(string1,pin,pinseq_string)

      pinlabel_string='Einc1'
      write(symbol_file_unit,'(A,4I6,A)')'P ',xpin1(end),ypin,xpin2(end),ypin,' 1 0 0'
      write(symbol_file_unit,'(A)')'{'
      write(symbol_file_unit,'(A)')'T 150 250   5 8 0 0 0 6 1'
      write(symbol_file_unit,'(A)')trim(pinnumber_string)
      write(symbol_file_unit,'(A)')'T 150 150   5 8 0 0 0 8 1'
      write(symbol_file_unit,'(A)')trim(pinseq_string)
      write(symbol_file_unit,'(A,2I6,A,I3,A)')'T ',xpin_label(end),ypin,' 9 6 1 1 0 ',align_label(end),' 1'
      write(symbol_file_unit,'(A)')trim(pinlabel_string)
      write(symbol_file_unit,'(A)')'T 200 200   5 8 0 0 0 2 1'
      write(symbol_file_unit,'(A)')'pintype=pas'
      write(symbol_file_unit,'(A)')'}'
    
! put the first Einc pin on the LHS of the symbol    
      end=2
      pin=pin+1
      ypin=ymax_symbol-ymax_offset-(n_conductors)*y_conductor_spacing
      
      string1='pinnumber='
      CALL add_integer_to_string(string1,pin,pinnumber_string)
      
      string1='pinseq='
      CALL add_integer_to_string(string1,pin,pinseq_string)

      pinlabel_string='Einc2'
      write(symbol_file_unit,'(A,4I6,A)')'P ',xpin1(end),ypin,xpin2(end),ypin,' 1 0 0'
      write(symbol_file_unit,'(A)')'{'
      write(symbol_file_unit,'(A)')'T 150 250   5 8 0 0 0 6 1'
      write(symbol_file_unit,'(A)')trim(pinnumber_string)
      write(symbol_file_unit,'(A)')'T 150 150   5 8 0 0 0 8 1'
      write(symbol_file_unit,'(A)')trim(pinseq_string)
      write(symbol_file_unit,'(A,2I6,A,I3,A)')'T ',xpin_label(end),ypin,' 9 6 1 1 0 ',align_label(end),' 1'
      write(symbol_file_unit,'(A)')trim(pinlabel_string)
      write(symbol_file_unit,'(A)')'T 200 200   5 8 0 0 0 2 1'
      write(symbol_file_unit,'(A)')'pintype=pas'
      write(symbol_file_unit,'(A)')'}'
    
  end if
  
!  spice_subcircuit_filename=trim(MOD_spice_bundle_lib_dir)//trim(spice_bundle_model%spice_model_name)//spice_model_file_extn
  spice_subcircuit_filename='PATH_TO_TRANSMISSION_LINE_SUB_CIRCUITS/'//  &
                            trim(spice_bundle_model%spice_model_name)//spice_model_file_extn
  
! write the general circuit symbol information
  write(symbol_file_unit,'(A,2I6,A)')'T ',(xmin_symbol+xmax_symbol)/2,ymax_symbol+2*ymax_text_offset,' 8 10 1 1 0 4 1'
  string1='device='//trim(spice_bundle_model%spice_model_name)  
  write(symbol_file_unit,'(A)')trim(string1)
  
  write(symbol_file_unit,'(A,2I6,A)')'T ',(xmin_symbol+xmax_symbol)/2,ymax_symbol+ymax_text_offset,' 5 10 1 0 0 4 1'
  write(symbol_file_unit,'(A)')'refdes=X?'

  write(symbol_file_unit,'(A,2I6,A)')'T ',xmin_symbol,ymin_symbol,' 8 10 0 0 0 4 1'
  string1='description='//trim(spice_bundle_model%spice_model_name)  
  write(symbol_file_unit,'(A)')trim(string1)

  write(symbol_file_unit,'(A,2I6,A)')'T ',xmin_symbol,ymin_symbol,' 8 10 0 0 0 0 1'
  string1='value='//trim(spice_bundle_model%spice_model_name)  
  write(symbol_file_unit,'(A)')trim(string1)

  write(symbol_file_unit,'(A,2I6,A)')'T ',xmin_symbol,ymin_symbol,' 8 10 0 0 0 0 1'
  write(symbol_file_unit,'(A,A)')'file=',trim(spice_subcircuit_filename)

  write(symbol_file_unit,'(A,2I6,A)')'T ',xmin_symbol,ymin_symbol,' 8 10 0 0 0 0 1'
  write(symbol_file_unit,'(A)')'numslots=0'

  write(symbol_file_unit,'(A,2I6,A)')'T ',xmin_symbol,ymin_symbol,' 8 10 0 0 0 0 1'
  write(symbol_file_unit,'(A)')'symversion=0.1'
  
! close the symbol file

  CLOSE(unit=symbol_file_unit)

  if (verbose) write(*,*)'Closed file:',trim(filename)

  RETURN

END SUBROUTINE create_spice_subcircuit_symbol_NGspice
!
! NAME
!     create_spice_subcircuit_symbol_LTspice
!
! AUTHORS
!     Chris Smartt
!
! DESCRIPTION
!     This subroutine creates a symbol for the Spice subcircuit model for the cable bundle
!     to be used in schematic capture software
!
!     The file formats for Gschem can be found here: http://wiki.geda-project.org/geda:file_format_spec
!     
! COMMENTS
!     
!
! HISTORY
!
!     started 20/3/2017 CJS
!     2/8/2017 CJS: change filename path for the library file to be 
!     something that must be edited by the user/ GUI software
!
!
SUBROUTINE create_spice_subcircuit_symbol_LTspice(spice_bundle_model)

USE type_specifications
USE general_module
USE constants
USE cable_module
USE cable_bundle_module
USE spice_cable_bundle_module
USE circuit_symbol_module

IMPLICIT NONE

! variables passed to the subroutine

TYPE(spice_model_specification_type),intent(IN) :: spice_bundle_model

! local variables

character(len=filename_length)    :: filename                    ! filename for the symbol file
character(len=filename_length)    :: spice_subcircuit_filename   ! filename for the associated spice sub-circuit model

integer :: n_conductors

integer :: LT_ymax_symbol    ! maximum y extent of the symbol (depends on the number of conductors)

integer :: LT_xpin1(2),LT_xpin2(2)  ! pin x coordinates for ends 1 and 2 of the transmission line symbol
integer :: LT_ypin                  ! pin y coordinate
integer :: Einc_y_offset

integer :: xpin_label(2)      ! x coordinate for conductor labels at ends 1 and 2 of the transmission line symbol

! loop variables
integer :: pin                ! pin number
integer :: end                ! end number
integer :: conductor          ! conductor number

! temporary strings
character(len=line_length)    :: string1
character(len=line_length)    :: string2

! pin label strings
character(len=line_length)    :: pinnumber_string
character(len=line_length)    :: pinseq_string
character(len=line_length)    :: pinlabel_string

! START
  
! filename for the symbol. The directory for the symbol is read from the 
! .spice_model_spec file (i.e. specified by the GUI)

  filename=trim(spice_symbol_dir)//trim(spice_bundle_model%spice_model_name)//symbol_file_extn

! open the symbol file
  
  OPEN(unit=symbol_file_unit,file=filename)

  if (verbose) write(*,*)'Opened file:',trim(filename)

! calculate the size of the symbol from the number of conductors and set all symbol dimensions

  n_conductors=spice_bundle_model%bundle%tot_n_conductors

  LT_ymax_symbol=LT_ymin_offset+(n_conductors-1)*LT_y_conductor_spacing+LT_ymax_offset
  
! add a space for the incident field nodes  
  Einc_y_offset=0
  if (spice_bundle_model%include_incident_field) then
    Einc_y_offset=LT_y_conductor_spacing
    LT_ymax_symbol=LT_ymax_symbol+Einc_y_offset
  end if

! end 1 pin parameters # this could maybe go with parameters in the module...
  LT_xpin1(1)=LT_xmin_symbol-LT_x_pin_length
  LT_xpin2(1)=LT_xmin_symbol
  
! end 2 pin parameters
  LT_xpin1(2)=LT_xmax_symbol+LT_x_pin_length
  LT_xpin2(2)=LT_xmax_symbol
  
 ! write the header
  write(symbol_file_unit,'(A)')LT_symbol_version
  write(symbol_file_unit,'(A)')'SymbolType CELL'

! write the rectangular box
  write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xmin_symbol,LT_ymin_symbol,LT_xmin_symbol,LT_ymax_symbol
  write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xmin_symbol,LT_ymax_symbol,LT_xmax_symbol,LT_ymax_symbol
  write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xmax_symbol,LT_ymax_symbol,LT_xmax_symbol,LT_ymin_symbol
  write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xmax_symbol,LT_ymin_symbol,LT_xmin_symbol,LT_ymin_symbol

! write the connection wires to the pin positions    
  pin=0
  do end=1,2
  
    do conductor=1,n_conductors
    
      pin=pin+1
      
      LT_ypin=LT_ymax_symbol-LT_ymax_offset-(n_conductors-conductor)*LT_y_conductor_spacing-Einc_y_offset
      
      write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xpin1(end),LT_ypin,LT_xpin2(end),LT_ypin
   
    end do ! next conductor
    
  end do ! other cable end
  
! add pins for the incident field nodes  
  if (spice_bundle_model%include_incident_field) then
  
    end=1
    pin=pin+1
      
    LT_ypin=LT_ymax_symbol-LT_ymax_offset
      
    write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xpin1(end),LT_ypin,LT_xpin2(end),LT_ypin
  
    end=2
    pin=pin+1
      
    LT_ypin=LT_ymax_symbol-LT_ymax_offset
      
    write(symbol_file_unit,'(A,4I6)')'LINE Normal ',LT_xpin1(end),LT_ypin,LT_xpin2(end),LT_ypin
    
  end if

! write general information

  write(symbol_file_unit,'(A,2I6,A)')'WINDOW 3 ',(LT_xmin_symbol+LT_xmax_symbol)/2,-LT_ymax_text_offset,' centre 0'
  
  string1='Value '//trim(spice_bundle_model%spice_model_name)  
  write(symbol_file_unit,'(A,A)')'SYMATTR ',trim(string1)
  
  string1='Prefix X'
  write(symbol_file_unit,'(A,A)')'SYMATTR ',trim(string1)
  
!  spice_subcircuit_filename=trim(MOD_spice_bundle_lib_dir)//trim(spice_bundle_model%spice_model_name)//spice_model_file_extn  
  spice_subcircuit_filename='PATH_TO_TRANSMISSION_LINE_SUB_CIRCUITS/'//  &
                            trim(spice_bundle_model%spice_model_name)//spice_model_file_extn
  string1='ModelFile '//trim(spice_subcircuit_filename)
  write(symbol_file_unit,'(A,A)')'SYMATTR ',trim(string1)
  
! write the connection pins    
  pin=0
  do end=1,2
  
    do conductor=1,n_conductors
    
      pin=pin+1
      LT_ypin=LT_ymax_symbol-LT_ymax_offset-(n_conductors-conductor)*LT_y_conductor_spacing-Einc_y_offset
      
      if (end.eq.1) then
        write(symbol_file_unit,'(A,2I6,A,I6)')'PIN ',LT_xpin1(end),LT_ypin,' LEFT ',LT_x_pin_length
      else
        write(symbol_file_unit,'(A,2I6,A,I6)')'PIN ',LT_xpin1(end),LT_ypin,' RIGHT ',LT_x_pin_length      
      end if
                
      string1='PinName c'      
      CALL add_integer_to_string(string1,conductor,string2)
      string1=trim(string2)//'_e'
      CALL add_integer_to_string(string1,end,pinlabel_string)
      write(symbol_file_unit,'(A,A)')'PINATTR ',trim(pinlabel_string)
         
      string1=''
      CALL add_integer_to_string(string1,pin,pinnumber_string)
      write(symbol_file_unit,'(A,A)')'PINATTR SpiceOrder ',trim(pinnumber_string)
   
    end do ! next conductor
    
  end do ! other cable end
  
  if (spice_bundle_model%include_incident_field) then
   
    end=1
    pin=pin+1     
    LT_ypin=LT_ymax_symbol-LT_ymax_offset
    write(symbol_file_unit,'(A,2I6,A,I6)')'PIN ',LT_xpin1(end),LT_ypin,' LEFT ',LT_x_pin_length
    pinlabel_string='PinName Einc1'
    write(symbol_file_unit,'(A,A)')'PINATTR ',trim(pinlabel_string)
    string1=''
    CALL add_integer_to_string(string1,pin,pinnumber_string)
    write(symbol_file_unit,'(A,A)')'PINATTR SpiceOrder ',trim(pinnumber_string)
  
    end=2
    pin=pin+1      
    write(symbol_file_unit,'(A,2I6,A,I6)')'PIN ',LT_xpin1(end),LT_ypin,' RIGHT ',LT_x_pin_length      
    pinlabel_string='PinName Einc2'
    write(symbol_file_unit,'(A,A)')'PINATTR ',trim(pinlabel_string)
    string1=''
    CALL add_integer_to_string(string1,pin,pinnumber_string)
    write(symbol_file_unit,'(A,A)')'PINATTR SpiceOrder ',trim(pinnumber_string)

  
  end if
  
  xpin_label(1)=LT_xmin_symbol
  xpin_label(2)=LT_xmax_symbol
  
! close the symbol file

  CLOSE(unit=symbol_file_unit)

  if (verbose) write(*,*)'Closed file:',trim(filename)

  RETURN

END SUBROUTINE create_spice_subcircuit_symbol_LTspice