Sunteți pe pagina 1din 14

394 Power systems electromagnetic transients simulation

!*******************************************************
SUBROUTINE XDot(SVV,DSVV)
!
.
!
X = [A]X+[B]U
!*******************************************************
!
!
!
!

SVV = State variable vector


DSVV = Derivative of state variable vector
X(1) = Capacitor Voltage
X(2) = Inductor Current
IMPLICIT NONE
INTEGER, PARAMETER:: RealKind_DP = SELECTED_REAL_KIND(15,307)
REAL (Kind = RealKind_DP) :: SVV(2),DSVV(2)
REAL (Kind = RealKind_DP) :: R,L,C,E
COMMON/COMPONENTS/R,L,C,E
DSVV(1) = SVV(2)/C
DSVV(2) =-SVV(1)/L-SVV(2)*R/L+E/L
RETURN
END

Appendix H

FORTRAN code for EMT simulation

H.1

DC source, switch and RL load

In this example a voltage step (produced by a switch closed on to a d.c. voltage


source) is applied to an RL Load. Results are shown in section 4.4.2. The RL load is
modelled by one difference equation rather than each component separately.
!====================================================================
PROGRAM EMT_Switch_RL
!====================================================================
IMPLICIT NONE
INTEGER, PARAMETER:: RealKind_DP = SELECTED_REAL_KIND(15,307)
INTEGER, PARAMETER:: Max_Steps = 5000
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL

(Kind
(Kind
(Kind
(Kind
(Kind
(Kind
(Kind
(Kind

=
=
=
=
=
=
=
=

RealKind_DP), PARAMETER :: pi = 3.141592653589793233D0


RealKind_DP) :: R,L,Tau
RealKind_DP) :: DeltaT,Time_Sec
RealKind_DP) :: K_i,K_v
RealKind_DP) :: R_switch,G_switch
RealKind_DP) :: V_source
RealKind_DP) :: I_inst,I_history
RealKind_DP) :: i(Max_Steps),v(Max_Steps),
v_load(Max_Steps)
REAL (Kind = RealKind_DP) :: R_ON,R_OFF
REAL (Kind = RealKind_DP) :: G_eff,Finish_Time
INTEGER :: k,m,ON,No_Steps

!
!

Initalize Variables
------------------Finish_Time = 1.0D-3
R = 1.0D0
L = 50.00D-6
V_source = 100.0
Tau = L/R
DeltaT = 50.0D-6

!
!
!
!
!
!

Seconds
Ohms
Henries
Volts
Seconds
Seconds

396 Power systems electromagnetic transients simulation


R_ON = 1.0D-10
R_OFF = 1.0D10
R_Switch = R_OFF
ON = 0

!
!
!
!

Ohms
Ohms
Ohms
Initially switch is open

m = 1
i(m) = 0.0
Time_Sec = 0.0
v(m) =100.0
v_load(m) = 0.0
K_i = (1-DeltaT*R/(2*L))/(1+DeltaT*R/(2*L))
K_v = (DeltaT/(2*L))/(1+DeltaT*R/(2*L))
G_eff = K_v
G_switch = 1.0/R_switch
OPEN (unit=10,status=unknown,file=SwitchRL1.out)
No_Steps= Finish_Time/DeltaT
IF(Max_Steps<No_Steps) THEN
STOP *** Too Many Steps ***
END IF
MainLoop: DO k=1,No_Steps,1
m=m+1
Time_Sec = k*DeltaT
!
!

Check Switch position


--------------------IF(k==3) THEN
ON = 1
R_switch = R_ON
G_switch = 1.0/R_switch
END IF

!
!

Update History term


------------------I_history = k_i*i(m-1) + k_v*v_load(m-1)

!
!

Update Voltage Sources


---------------------v(m) = V_source

!
!

Solve for V and I


----------------v_load(m) = (-I_history + v(m)* G_switch)/(G_eff+G_Switch)
I_inst
= v_load(m)*G_eff
i(m)
= I_inst + I_history
write(10,*) Time_Sec,v_load(m),i(m)
END DO MainLoop
CLOSE(10)
PRINT *, Execution Finished

END PROGRAM EMT_Switch_RL

FORTRAN code for EMT simulation 397

H.2

General EMT program for d.c. source, switch and RL load

The same case as in section H.1 is modelled here, however, the program is now
structured in a general manner, where each component is subjected to numerical
integrator substitution (NIS) and the conductance matrix is built up. Moreover, rather
than modelling the switch as a variable resistor, matrix partitioning is applied (see
section 4.4.1), which enables the use of ideal switches.
!===============================
!
PROGRAM EMT_Switch_RL
!
! Checked and correct 4 May 2001
!===============================
IMPLICIT NONE
! INTEGER SELECT_REAL_KIND
!INTEGER ,PARAMETER:: Real_18_4931 =SELECT_REAL_KIND(P=18,R=4931)
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8
REAL*8

::
::
::
::
::
::
::
::
::
::

R,L,Tc
DeltaT
i_L,i_R,i_Source,i_Source2
R_switch,G_switch
G(3,3),v(3),I_Vector(2)
G_L,G_R
V_source
I_L_history
Multiplier
R_ON,R_OFF

INTEGER k,n,NoTimeSteps
INTEGER NoColumns
open(unit=11,status=unknown,file=vi.out)
NoTimeSteps = 6
NoColumns = 3
R_ON = 1.0D-10
R_OFF = 1.0D+10

! Ohms
! Ohms

DeltaT = 50.0D-6 ! Seconds


R = 1.0D0
! Ohms
L = 50.00D-6
! Henries
V_source=100
! Volts
Tc = L/R
PRINT *,Time Constant=,Tc
R_switch = R_OFF
G_switch = 1/R_switch
G_R = 1/R
G_L = DeltaT/(2*L) ! G_L_eff

398 Power systems electromagnetic transients simulation


!
!

Initialize Variables
-------------------I_Vector(1) =0.0D0
I_Vector(2) =0.0D0
i_L =0.0D0
DO k=1,3
v(k) = 0.000D0
END DO

!
!

Form System Conductance Matrix


-----------------------------CALL Form_G(G_R,G_L,G_switch,G)

!
!

Forward Reduction
----------------CALL Forward_Reduction_G(NoColumns,G,Multiplier)

!
!

Enter Main Time-stepping loop


----------------------------DO n=1,NoTimeSteps
IF(n==1)THEN
write(10, *) Switch Turned ON
R_switch = R_ON
G_switch = 1/R_switch
CALL Form_G(G_R,G_L,G_switch,G)
CALL Forward_Reduction_G(NoColumns,G,Multiplier)
END IF

!
!

Calculate Past History Terms


---------------------------I_L_history =i_L + v(3)*G_L
I_Vector(1) = 0.0
I_Vector(2) = -I_L_history

!
!

Update Source Values


-------------------V_source = 100.0
V(1) = V_source

!
!

Forward Reduction of Current Vector


----------------------------------I_Vector(2) = I_Vector(2) - Multiplier*I_Vector(1)

!
!

Move Known Voltage to RHS (I_current Vector)


-------------------------------------------I_Vector(1) = I_Vector(1)- G(1,3) * V(1)
I_Vector(2) = I_Vector(2)- G(2,3) * V(1)

!
!

Back-substitution
----------------v(3) = I_Vector(2)/G(2,2)
v(2) = (I_Vector(1)-G(1,2)*v(3))/G(1,1)

FORTRAN code for EMT simulation 399


!
!

Calculate Branch Current


-----------------------i_R = (v(2) - v(3))/R
i_L = v(3)*G_L + I_L_history
i_Source2 = (v(1)-v(2))*G_switch
i_Source = G(3,1)*v(2) + G(3,2)*v(3) + G(3,3)*v(1)
WRITE(11,1160) n*DeltaT,v(1),v(2),v(3),i_Source,i_R,i_L

END DO
close(11)
1160 FORMAT(1X,F8.6,1X,6(G16.10,1X))
STOP
END
!====================================================
SUBROUTINE Form_G(G_R,G_L,G_switch,G)
!====================================================
IMPLICIT NONE
REAL*8 :: G(3,3)
REAL*8 :: G_L,G_R,G_switch
G(1,1) = G_switch + G_R
G(2,1) = - G_R
G(1,2) = - G_R
G(2,2) = G_L + G_R
G(1,3) = -G_switch
G(2,3) = 0.0D0
G(3,1) =
G(3,2) =
G(3,3) =

-G_switch
0.0D0
G_switch

CALL Show_G(G)
RETURN
END
!====================================================
SUBROUTINE Forward_Reduction_G(NoColumns,G,Multiplier)
!====================================================
IMPLICIT NONE
REAL*8 :: G(3,3)
REAL*8 :: Multiplier
INTEGER :: k,NoColumns
Multiplier = G(2,1)/G(1,1)
PRINT *, Multiplier= ,Multiplier
DO k=1,NoColumns
G(2,k) = G(2,k) - Multiplier*G(1,k)
END DO
RETURN
END

400 Power systems electromagnetic transients simulation


!====================================================
SUBROUTINE Show_G(G)
!====================================================
IMPLICIT NONE
REAL*8 :: G(3,3)
WRITE(10,*) Matrix
WRITE(10,2000) G(1,1:3)
WRITE(10,2000) G(2,1:3)
2000 FORMAT(1X,[,G16.10, ,G16.10, ,G16.10,])
RETURN
END

H.3

AC source diode and RL load

This program is used to demonstrate the numerical oscillation that occurs at turn-off,
by modelling an RL load fed from an a.c. source through a diode. The RL load
is modelled by one difference equation rather than each component separately. The
results are given in section 9.4.
!====================================================================
PROGRAM EMT_DIODE_RL1
!====================================================================
IMPLICIT NONE
INTEGER, PARAMETER:: RealKind_DP = SELECTED_REAL_KIND(15,307)
INTEGER, PARAMETER:: Max_Steps = 5000
REAL (Kind = RealKind_DP), PARAMETER :: pi = 3.141592653589793233D0
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL

(Kind
(Kind
(Kind
(Kind
(Kind
(Kind
(Kind
(Kind
(Kind

=
=
=
=
=
=
=
=
=

RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)
RealKind_DP)

INTEGER :: k,m,ON,No_Steps

::
::
::
::
::
::
::
::
::

!
!

Initalize Variables
------------------f=50.0
Finish_Time = 60.0D-3
R = 100.0
L = 500D-3
Tau = L/R
DeltaT = 50.0D-6
V_mag = 230.0*sqrt(2.)
V_ang = 0.0

R,L,Tau,f
DeltaT,Time_Sec
K_i,K_v
R_switch,G_switch
V_mag,V_ang
I_inst,I_history
i(Max_Steps),v(Max_Steps),v_load(Max_Steps)
R_ON,R_OFF
G_eff,Finish_Time

FORTRAN code for EMT simulation 401

R_ON = 1.0D-10
R_OFF = 1.0D10
R_Switch = R_ON
m=1
i(m) = 0.0
Time_Sec = 0.0
v(m) = V_mag*sin(V_ang*pi/180)
v_load(m)=v(m)
ON=1
K_i = (1-DeltaT*R/(2*L))/(1+DeltaT*R/(2*L))
K_v = (DeltaT/(2*L))/(1+DeltaT*R/(2*L))
G_eff = K_v
G_switch = 1.0/R_switch
OPEN (unit=10,status=unknown,file=DiodeRL1.out)
No_Steps= Finish_Time/DeltaT
IF(Max_Steps<No_Steps) THEN
STOP *** Too Many Steps ***
END IF
MainLoop: DO k=1,No_Steps,1
m=m+1
Time_Sec = k*DeltaT
!
!

Check Switch position


--------------------IF (i(m-1)<= 0.0 .and. ON==1 .and. k >5*DeltaT) THEN
ON = 0
R_switch = R_OFF
G_switch = 1.0/R_switch
i(m-1)
= 0.0
END IF
IF (v(m-1)-v_load(m-1) > 1.0 .and. ON==0) THEN
ON = 1
R_switch = R_ON
G_switch = 1.0/R_switch
END IF

!
!

Update History term


------------------I_history = k_i*i(m-1) + k_v*v_load(m-1)

!
!

Update Voltage Sources


---------------------v(m) =
V_mag*sin(2*pi*f*Time_Sec + V_ang*pi/180)

!
!

Solve for V and I


----------------v_load(m) = (-I_history + v(m)* G_switch)/(G_eff+G_Switch)
I_inst
= v_load(m)*G_eff

402 Power systems electromagnetic transients simulation


i(m)
= I_inst + I_history
write(10,*) Time_Sec,v_load(m),i(m)
END DO MainLoop
CLOSE(10)
PRINT *, Execution Finished
END PROGRAM EMT_DIODE_RL1

H.4

Simple lossless transmission line

This program evaluates the step response of a simple lossless transmission line, as
shown in section 6.6.
!==========================================================
PROGRAM Lossless_TL
!
! A simple lossless travelling wave transmission line
!==========================================================
IMPLICIT NONE
INTEGER, PARAMETER:: RealKind_DP = SELECTED_REAL_KIND(15,307)
INTEGER, PARAMETER:: TL_BufferSize = 100
!
!

Transmission Line Buffer


-----------------------REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::

Vsend(TL_BufferSize)
Vrecv(TL_BufferSize)
Isend_Hist(TL_BufferSize)
Irecv_Hist(TL_BufferSize)

REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL

L_dash,C_dash,Length
DeltaT
Time
R_Source,R_Load
V_Source,I_Source
Gsend,Grecv,Rsend,Rrecv
Zc, Gamma
Finish_Time,Step_Time
i_send ! Sending to Receiving end current
i_recv ! Receiving to Sending end current

(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)

INTEGER
INTEGER
INTEGER
INTEGER

::
::
::
::
::
::
::
::
::
::

Position
PreviousHistoryPSN
k,NumberSteps,Step_No
No_Steps_Delay

OPEN(UNIT=10,file=TL.out,status="UNKNOWN")
!
!

Default Line Parameters


----------------------L_dash = 400D-9

FORTRAN code for EMT simulation 403


C_dash = 40D-12
Length = 2.0D5
DeltaT = 50D-6
R_Source = 0.1
R_Load = 100.0
Finish_Time = 10.0D-3
Step_Time=5*DeltaT
CALL ReadTLData(L_dash,C_Dash,Length,DeltaT,R_Source,R_Load,
Step_Time,Finish_Time)
Zc = sqrt(L_dash/C_dash)
Gamma = sqrt(L_dash*C_dash)
No_Steps_Delay = Length*Gamma/DeltaT
!
!

Write File Header Information


----------------------------WRITE(10,10) L_dash,C_dash,Length,Gamma,Zc
WRITE(10,11) R_Source,R_Load,DeltaT,Step_Time
10 FORMAT(1X,% L =,G16.6, C =,G16.6, Length=,F12.2,
Propagation Constant=,G16.6, Zc=,G16.6)
11 FORMAT(1X,% R_Source =,G16.6, R_Load =,G16.6, DeltaT=,F12.6,
Step_Time=,F12.6)
Gsend
Rsend
Grecv
Rrecv
!

=
=
=
=

1.0D0/ R_Source + 1.0D0/Zc


1.0D0/Gsend
1.0D0/ R_Load + 1.0D0/Zc
1.0D0/Grecv

Initialize Buffers
DO k=1,TL_BufferSize
Vsend(k) = 0.0D0
Vrecv(k) = 0.0D0
Isend_Hist(k) = 0.0D0
Irecv_Hist(k) = 0.0D0
END DO
Position = 0
NumberSteps = NINT(Finish_Time/DeltaT)

!
!

DO Time = DeltaT,Finish_Time,DeltaT (Note REAL DO loop variables


removed in FORTRAN95)
DO Step_No = 1,NumberSteps,1
Time = DeltaT*Step_No
Position = Position+1

!
!

Make sure index the correct values in Ring Buffer


------------------------------------------------PreviousHistoryPSN = Position - No_Steps_Delay
IF(PreviousHistoryPSN>TL_BufferSize) THEN
PreviousHistoryPSN = PreviousHistoryPSN-TL_BufferSize
ELSE IF(PreviousHistoryPSN<1) THEN
PreviousHistoryPSN = PreviousHistoryPSN+TL_BufferSize
END IF

404 Power systems electromagnetic transients simulation


IF(Position>TL_BufferSize) THEN
Position = Position-TL_BufferSize
END IF

!
!

Update Sources
-------------IF(Time< 5*DeltaT) THEN
V_Source = 0.0
ELSE
V_Source = 100.0
END IF
I_Source = V_Source/R_Source

!
!

Solve for Nodal Voltages


-----------------------Vsend(Position) = (I_Source-Isend_Hist(PreviousHistoryPSN))*Rsend
Vrecv(Position) = (
-Irecv_Hist(PreviousHistoryPSN))*Rrecv

!
!

Solve for Terminal Current


-------------------------i_send = Vsend(Position)/Zc + Isend_Hist(PreviousHistoryPSN)
i_recv = Vrecv(Position)/Zc + Irecv_Hist(PreviousHistoryPSN)

!
!

Calculate History Term (Current Source at tau later).


----------------------------------------------------Irecv_Hist(Position) = (-1.0/Zc)*Vsend(Position) - i_send
Isend_Hist(Position) = (-1.0/Zc)*Vrecv(Position) - i_recv

WRITE(10,1000) Time,Vsend(Position),Vrecv(Position),i_send,i_recv,
Isend_Hist(Position),Irecv_Hist(Position)
END DO
1000 FORMAT(1X,7(G16.6,1X))
CLOSE(10)
PRINT *, Successful Completion
END

H.5

Bergeron transmission line

In this example the step response of a simple transmission line with lumped losses
(Bergeron model) is evaluated (see section 6.6).
!==========================================================
PROGRAM TL_Bergeron
! Bergeron Line Model (Lumped representation of Losses)
!==========================================================
IMPLICIT NONE
INTEGER, PARAMETER:: RealKind_DP = SELECTED_REAL_KIND(15,307)
INTEGER, PARAMETER:: TL_BufferSize = 100

FORTRAN code for EMT simulation 405

!
!

Transmission Line Buffer


-----------------------REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::
REAL (Kind=RealKind_DP) ::

Vsend(TL_BufferSize)
Vrecv(TL_BufferSize)
Isend_Hist(TL_BufferSize)
Irecv_Hist(TL_BufferSize)

REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL
REAL

R_dash,L_dash,C_dash,Length
DeltaT,Time
R,R_Source,R_Load
V_Source,I_Source
Gsend,Grecv,Rsend,Rrecv
Zc, Zc_Plus_R4,Gamma
Finish_Time,Step_Time
i_send ! Sending to Receiving end current
i_recv ! Receiving to Sending end current

(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)
(Kind=RealKind_DP)

INTEGER
INTEGER
INTEGER
INTEGER

::
::
::
::
::
::
::
::
::

Position
PreviousHistoryPSN
k,NumberSteps,Step_No
No_Steps_Delay

OPEN(UNIT=10,file=TL.out,status="UNKNOWN")
R_dash = 100D-6
L_dash = 400D-9
C_dash = 40D-12
Length = 2.0D5
DeltaT = 50D-6
R_Source = 0.1
R_Load = 100.0
Finish_Time = 1.0D-4
Step_Time=5*DeltaT
CALL ReadTLData(R_dash,L_dash,C_Dash,Length,DeltaT,R_Source,
R_Load,Step_Time,Finish_Time)
R=R_Dash*Length
Zc = sqrt(L_dash/C_dash)
Gamma = sqrt(L_dash*C_dash)
No_Steps_Delay = Length*Gamma/DeltaT
Zc_Plus_R4 = Zc+R/4.0
!
!

Write File Header Information


----------------------------WRITE(10,10) R_dash,L_dash,C_dash,Length,Gamma,Zc
WRITE(10,11) R_Source,R_Load,DeltaT,Step_Time
10 FORMAT(1X,% R =,G16.6, L =,G16.6, C =,G16.6, Length=,F12.2,
Propagation Constant=,G16.6, Zc=,G16.6)
11 FORMAT(1X,% R_Source =,G16.6, R_Load =,G16.6, DeltaT=,F12.6,
Step_Time=,F12.6)

406 Power systems electromagnetic transients simulation

Gsend
Rsend
Grecv
Rrecv

=
=
=
=

1.0D0/ R_Source + 1.0D0/Zc_Plus_R4


1.0D0/Gsend
1.0D0/ R_Load + 1.0D0/Zc_Plus_R4
1.0D0/Grecv

DO k=1,TL_BufferSize
Vsend(k) = 0.0D0
Vrecv(k) = 0.0D0
Isend_Hist(k) = 0.0D0
Irecv_Hist(k) = 0.0D0
END DO
Position = 0
Position = 0
NumberSteps = NINT(Finish_Time/DeltaT)
DO Step_No = 1,NumberSteps,1
Time = DeltaT*Step_No
Position = Position+1
!
!

Make sure index the correct values in Ring Buffer


------------------------------------------------PreviousHistoryPSN = Position - No_Steps_Delay
IF(PreviousHistoryPSN>TL_BufferSize) THEN
PreviousHistoryPSN = PreviousHistoryPSN-TL_BufferSize
ELSE IF(PreviousHistoryPSN<1) THEN
PreviousHistoryPSN = PreviousHistoryPSN+TL_BufferSize
END IF
IF(Position>TL_BufferSize) THEN
Position = Position-TL_BufferSize
END IF

!
!

Update Sources
-------------IF(Time< 5*DeltaT) THEN
V_Source = 0.0
ELSE
V_Source = 100.0
END IF
I_Source = V_Source/R_Source

!
!

Solve for Nodal Voltages


-----------------------Vsend(Position) = (I_Source-Isend_Hist(PreviousHistoryPSN))*Rsend
Vrecv(Position) = (
-Irecv_Hist(PreviousHistoryPSN))*Rrecv
WRITE(12,1200)Time,Position,PreviousHistoryPSN,
Isend_Hist(PreviousHistoryPSN),Irecv_Hist(PreviousHistoryPSN)
1200 FORMAT(1X,G16.6,1X,I5,1X,I5,2(G16.6,1X))

FORTRAN code for EMT simulation 407


!
!

Solve for Terminal Current


-------------------------i_send = Vsend(Position)/Zc_Plus_R4 + Isend_Hist(PreviousHistoryPSN)
i_recv = Vrecv(Position)/Zc_Plus_R4 + Irecv_Hist(PreviousHistoryPSN)

!
!

Calculate History Term (Current Source at tau later).


----------------------------------------------------Irecv_Hist(Position) = (-Zc/(Zc_Plus_R4**2))*(Vsend(Position)
+(Zc-R/4.0)*i_send) &
+((-R/4.0)/(Zc_Plus_R4**2))
*(Vrecv(Position)+(Zc-R/4.0)*i_recv)
Isend_Hist(Position) = (-Zc/(Zc_Plus_R4**2))*(Vrecv(Position)
+(Zc-R/4.0)*i_recv) &
+((-R/4.0)/(Zc_Plus_R4**2))
*(Vsend(Position)+(Zc-R/4.0)*i_send)

WRITE(10,1000) Time,Vsend(Position),Vrecv(Position),
i_send,i_recv,Isend_Hist(Position),Irecv_Hist(Position)
END DO
1000 FORMAT(1X,7(G16.6,1X))
CLOSE(10)
PRINT *, Successful Completion
END

H.6

Frequency-dependent transmission line

This program demonstrates the implementation of a full frequency-dependent transmission line and allows the step response to be determined. This is an s-domain
implementation using recursive convolution. For simplicity interpolation of buffer
values is not included. Results are illustrated in section 6.6.
!==========================================================
PROGRAM TL_FDP_s
!
! Simple Program to demonstrate the implementation of a
! Frequency-Dependent Transmission Line using s-domain representation.
!
!
Isend(w)
Irecv(w)
!
------>---------<----!
|
|
!
--------------!
|
|
|
|
!
_|__
/
/
_|__
!
| | /
/
| |
! Vs(w)
|Yc|
| /
| / |Yc|
Vr(w)
!
|__|
/
/
|__|
!
|
| Ih_s
| Ih_r |
!
--------------!
|
|
!
---------------------!
!==========================================================

S-ar putea să vă placă și