! ! 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: ! SUBROUTINE ML_flex_cable_set_parameters ! SUBROUTINE ML_flex_cable_set_internal_domain_information ! SUBROUTINE ML_flex_cable_plot ! ! NAME ! ML_flex_cable_set_parameters ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! Set the overall parameters for a ML_flex_cable cable ! ! COMMENTS ! ! ! HISTORY ! ! started 26/9/2016 CJS ! 16/11/2017 CJS Include network synthesis process to replace s-domain transfer functions ! ! SUBROUTINE ML_flex_cable_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_ML_flex_cable cable%tot_n_conductors=0 ! this is set in the cable specification file cable%tot_n_domains=1 cable%n_external_conductors=0 ! this is set in the cable specification file cable%n_internal_conductors=0 cable%n_internal_domains=0 cable%n_parameters=0 cable%n_dielectric_filters=1 cable%n_transfer_impedance_models=0 END SUBROUTINE ML_flex_cable_set_parameters ! ! NAME ! ML_flex_cable_set_internal_domain_information ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! Set the overall parameters for a ML_flex_cable 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 ! 8/5/2017 CJS: Include references to Theory_Manual ! ! SUBROUTINE ML_flex_cable_set_internal_domain_information(cable) USE type_specifications USE general_module USE constants IMPLICIT NONE ! variables passed to subroutine type(cable_specification_type),intent(INOUT) :: cable ! local variables integer :: nc integer :: dim integer :: i,prow,prow2,row2,row,col,conductivity_row real(dp) :: full_width,ML_flex_cable_xmin ! variables for cable parameter checks logical :: cable_spec_error real(dp) :: wd ! dielectric width real(dp) :: hd ! dielectric height integer :: nrows ! number of rows of conductors real(dp) :: w ! conductor width real(dp) :: h ! conductor height real(dp) :: s ! conductor separation real(dp) :: ox ! conductor offset x real(dp) :: oy ! conductor offset y integer :: ncrow ! number of conductors in this row integer :: conductor ! counter for conductors real(dp) :: w1,h1,w2,h2,ox1,ox2,oy1,oy2 real(dp) :: sigma type(Sfilter) :: epsr integer :: nclocal character(LEN=error_message_length) :: message character(LEN=2) :: conductor_string integer :: check_type ! START nc=cable%tot_n_conductors ! set the information related ot the number of conductors cable%n_external_conductors=nc ! Set the domain decomposition matrices ! Theory_Manual_Eqn 6.17, 6.18 ! The dimension of the domain transformation matrices is the number of conductors+1 dim=nc+1 cable%MI%dim=dim ALLOCATE(cable%MI%mat(dim,dim)) cable%MI%mat(:,:)=0d0 cable%MV%dim=dim ALLOCATE(cable%MV%mat(dim,dim)) cable%MV%mat(:,:)=0d0 do i=1,nc row=i col=row cable%MI%mat(row,col)=1d0 end do do i=1,dim row=dim col=i cable%MI%mat(row,col)=1d0 end do do i=1,nc row=i col=row cable%MV%mat(row,col)=1d0 cable%MV%mat(row,dim)=-1d0 end do cable%MV%mat(dim,dim)=1d0 ! Set the local reference conductor numbering ALLOCATE( cable%local_reference_conductor(nc) ) cable%local_reference_conductor(1:nc)=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)=nc+1 ! external domain ! Read the parameter list and set the conductor information nrows=NINT(cable%parameters(3)) ! check that the number of conductors is consistent prow=3 nclocal=0 do row=1,nrows ! loop over rows of conductors ncrow=NINT(cable%parameters(prow+6)) nclocal=nclocal+ncrow prow=prow+6 end do ! next row of conductors ! check that the number of conductors is consistent if (nclocal.NE.nc) then write(message,*)' Nc in .cable file=',nc,' conductor count=',nclocal run_status='ERROR in cable_model_builder, inconsistent conductor count for flex_cable:' & //trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if ! conductivity for the conductor loss models conductivity_row=prow+1 sigma=cable%parameters(conductivity_row) ! conductivity ALLOCATE( cable%external_model(cable%n_external_conductors) ) prow=3 conductor=0 ! reset the conductor count do row=1,nrows ! loop over rows of conductors ! get the parameters for this row of conductors ox=cable%parameters(prow+1) ! conductor offset in x oy=cable%parameters(prow+2) ! conductor offset in y w=cable%parameters(prow+3) ! conductor width h=cable%parameters(prow+4) ! conductor height s=cable%parameters(prow+5) ! conductor separation ncrow=NINT(cable%parameters(prow+6)) full_width=w*ncrow+s*(ncrow-1) ML_flex_cable_xmin=-full_width/2d0 do i=1,ncrow ! loop over the conductors in this row conductor=conductor+1 ! set the conductor impedance model for this conductor cable%conductor_impedance(conductor)%impedance_model_type=impedance_model_type_rectangular_with_conductivity cable%conductor_impedance(conductor)%width=w cable%conductor_impedance(conductor)%height=h cable%conductor_impedance(conductor)%conductivity=sigma ! Set the external domain conductor information CALL reset_external_conductor_model(cable%external_model(conductor)) cable%external_model(conductor)%conductor_type=rectangle cable%external_model(conductor)%conductor_width=w cable%external_model(conductor)%conductor_width2=w cable%external_model(conductor)%conductor_height=h ! work out the offset of the ith conductor cable%external_model(conductor)%conductor_ox=ox+ML_flex_cable_xmin+(w+s)*(i-1)+w/2d0 cable%external_model(conductor)%conductor_oy=oy end do ! next conductor in this row prow=prow+6 end do ! next row of conductors ! dielectric data epsr=cable%dielectric_filter(1) wd=cable%parameters(1) ! dielectric width hd=cable%parameters(2) ! dielectric height ! do some consistency checks cable_spec_error=.FALSE. ! assume no errors initially message='' ! Do some intersection checks on the flex cable prow=3 do row=1,nrows ! loop over rows of conductors ! get the parameters for this row of conductors ox1=cable%parameters(prow+1) ! conductor offset in x oy1=cable%parameters(prow+2) ! conductor offset in y w=cable%parameters(prow+3) ! conductor width h1=cable%parameters(prow+4) ! conductor height s=cable%parameters(prow+5) ! conductor separation ncrow=NINT(cable%parameters(prow+6)) w1=w*ncrow+s*(ncrow-1) ! w1 is the full width of the row of conductors ! check whether this row of conductors is well specified - conductor width, height and spearation >0 CALL flex_cable_check(ncrow,w,h1,s,0d0,0d0,cable_spec_error,cable%cable_name,message) if (cable_spec_error) then run_status='ERROR in cable_model_builder, error on parameters for cable:'//trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if ! check whether this row of conductors intersects the dielectric boundary of the flex cable check_type=2 CALL ML_flex_cable_check(w1,h1,ox1,oy1,wd,hd,0d0,0d0,check_type,cable_spec_error,cable%cable_name,message) if (cable_spec_error) then run_status='ERROR in cable_model_builder, error on parameters for cable:'//trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if ! loop over all the other rows to check for intersections between the rows of conductors prow=prow+6 prow2=prow do row2=row+1,nrows ! get the parameters for this row of conductors ox2=cable%parameters(prow2+1) ! conductor offset in x oy2=cable%parameters(prow2+2) ! conductor offset in y w=cable%parameters(prow2+3) ! conductor width h2=cable%parameters(prow2+4) ! conductor height s=cable%parameters(prow2+5) ! conductor separation ncrow=NINT(cable%parameters(prow2+6)) w2=w*ncrow+s*(ncrow-1) ! w2 is the full width of the second row of conductors ! check whether the two rows of conductors intersect check_type=1 CALL ML_flex_cable_check(w1,h1,ox1,oy1,w2,h2,ox2,oy2,check_type,cable_spec_error,cable%cable_name,message) if (cable_spec_error) then run_status='ERROR in cable_model_builder, error on parameters for cable:'//trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if prow2=prow2+6 end do ! next row2 for checking intersection between rows of conductors end do ! next row of conductors to check CALL dielectric_check(epsr,cable_spec_error,cable%cable_name,message) if (cable_spec_error) then run_status='ERROR in cable_model_builder, error on parameters for cable:'//trim(cable%cable_name)//'. '//trim(message) CALL write_program_status() STOP 1 end if ! add a dielectric region to the first conductor which encloses the whole cable ! write the dielectric which is offset from the conductors ! The dielectric is centred at the cable centre cable%external_model(1)%dielectric_width=wd cable%external_model(1)%dielectric_height=hd cable%external_model(1)%dielectric_ox=0d0 cable%external_model(1)%dielectric_oy=0d0 cable%external_model(1)%dielectric_epsr=epsr CALL deallocate_Sfilter(epsr) ALLOCATE( cable%conductor_label(1:cable%tot_n_conductors) ) do i=1,cable%tot_n_conductors write(conductor_string,'(I2)')i cable%conductor_label(i)='Cable name: '//trim(cable%cable_name)// & '. type: '//trim(cable%cable_type_string)//'. conductor '//conductor_string//' : ML_flex_cable conductor' end do END SUBROUTINE ML_flex_cable_set_internal_domain_information ! ! NAME ! ML_flex_cable_plot ! ! AUTHORS ! Chris Smartt ! ! DESCRIPTION ! plot ML_flex_cable cable ! ! COMMENTS ! ! ! HISTORY ! ! started 23/9/2016 CJS ! ! SUBROUTINE ML_flex_cable_plot(cable,x_offset,y_offset,theta,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 real(dp),intent(INOUT) :: xmin,xmax,ymin,ymax ! local variables integer nc real(dp) :: full_width,ML_flex_cable_xmin real(dp) :: xoff,yoff,x,y,w,h,s,wd,hd,ox,oy integer nrows,ncrow,row,prow integer i ! START ! plot ML_flex_cable conductor nc=cable%tot_n_conductors nrows=NINT(cable%parameters(3)) prow=3 do row=1,nrows ! loop over rows of conductors ! get the parameters for this row of conductors ox=cable%parameters(prow+1) ! conductor offset in x oy=cable%parameters(prow+2) ! conductor offset in y w=cable%parameters(prow+3) ! conductor width h=cable%parameters(prow+4) ! conductor height s=cable%parameters(prow+5) ! conductor separation ncrow=NINT(cable%parameters(prow+6)) full_width=w*ncrow+s*(ncrow-1) ML_flex_cable_xmin=-full_width/2d0 do i=1,ncrow ! loop over the conductors in this row ! work out the centre of this conductor before rotation xoff=ox+ML_flex_cable_xmin+(w+s)*(i-1)+w/2d0 yoff=oy ! work out the centre of this conductor when the flex cable is rotated and offset x=x_offset+xoff*cos(theta)-yoff*sin(theta) y=y_offset+xoff*sin(theta)+yoff*cos(theta) ! write the conductor CALL write_rectangle(x,y,w,h,theta,conductor_geometry_file_unit,xmin,xmax,ymin,ymax) end do ! next conductor in this row prow=prow+6 end do ! next row of conductors ! write the dielectric which is offset from the conductors wd=cable%external_model(1)%dielectric_width hd=cable%external_model(1)%dielectric_height CALL write_rectangle(x_offset,y_offset,wd,hd,theta,dielectric_geometry_file_unit,xmin,xmax,ymin,ymax) RETURN END SUBROUTINE ML_flex_cable_plot