|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126 |
- subroutine RTable_dia(x1,x2,x3,x5,x6,x7)
-
- use equipments_PowerLimit
- use RTable_VARIABLES
-
- IMPLICIT NONE
-
- REAL :: x1,x2,x3,x5,x6,x7
-
-
- !RTable%Vt = x6+Kpi*(Kpn*((30.*RTable%w_ref/pi)-(30.*x3/pi))-x2)
-
- RTable%ia_ref = x7+Kpn*((30.*RTable%w_ref/pi)-(30.*x3/pi))
-
- call RTTorqueLimit
- !if (LimitOveride==1) then
- ! goto TorqueLimit_Limitation1
- !end if
-
- !IF (RTable%ia_ref>RTable%ia_ref_limit) THEN
- ! RTable%ia_ref = RTable%ia_ref_limit
- !END IF
-
- !TorqueLimit_Elimination1:
-
- !call PowerLimits
- !if (Power_sigma>max_Power_sigma) then
- ! RTable%Vt = RTable%Vt
- !else
- RTable%Vt = x6+(Kpi*(RTable%ia_ref-x2))
- !end if
-
- IF (RTable%Vt>810.) THEN
- RTable%Vt = 810.0
- ELSE IF (RTable%Vt<0.) THEN
- RTable%Vt = 0.0
- END IF
-
-
- !IF (x2<=1150.) THEN
- x5 = (6.3304d-3)*1150.
- !ELSE IF (x2>1150.) THEN
- ! x5 = 2.8571d-7*(x2-1150.)+7.28
- !END IF
-
- RTable%Ea = x5*x3
- RTable%dia = (RTable%Vt-(Ra+Rf)*x2-RTable%Ea)/(La+Lf)
- !call PowerLimits
- !if (Power_sigma>max_Power_sigma) then
- ! RTable%dia = 0.d0
- !end if
-
- end subroutine
-
-
-
-
- !-------------------------------------------------------------------------------
- subroutine RTable_dw(x1,x2,x3,x4,x5)
-
- use RTable_VARIABLES
-
- IMPLICIT NONE
- REAL :: x1,x2,x3,x4,x5
- REAL :: const
-
- !IF (x2<=1150.) THEN
- x4 = 6.3304d-3*1150.
- !ELSE IF (x2>1150.) THEN
- ! x4 = 2.8571d-7*(x2-1150.)+7.28
- !END IF
-
- RTable%Te = x4*x2
- !RTable%dw = (RTable%Te-x5)/RTable%J_coef
-
- const = RTable%J_coef+(RTable%String_JCoef/(RTable%Mech_Efficiency*RTable%Conv_Ratio))
-
- !RTable%dw = (RTable%Te-((RTable%String_Torque)/(RTable%Mech_Efficiency*RTable%Conv_Ratio)))/(const)
- RTable%dw = (RTable%Te-RTable%TL)/(const)
-
- end subroutine
-
-
-
-
- !------------------------------------------------------------
- subroutine RTable_dx(x1,x2,x3,x4,x5)
-
- use RTable_VARIABLES
-
- IMPLICIT NONE
- REAL :: x1,x2,x3,x4,x5
-
- !RTable%dx = Kii*(Kpn*((30.*RTable%w_ref/pi)-(30.*x3/pi))-x2)
-
- RTable%ia_ref = x5+Kpn*((30.*RTable%w_ref/pi)-(30.*x3/pi))
-
- call RTTorqueLimit
- !if (LimitOveride==1) then
- !goto TorqueLimit_Limitation2
- !end if
-
- !IF (RTable%ia_ref>RTable%ia_ref_limit) THEN
- !RTable%ia_ref = RTable%ia_ref_limit
- !END IF
-
- !TorqueLimit_Elimination2:
-
- RTable%dx = Kii*(RTable%ia_ref-x2)
-
- end subroutine
-
-
-
-
- !------------------------------------------------------------
- subroutine RTable_dy(x1,x2,x3,x4,x5)
-
- use RTable_VARIABLES
-
- IMPLICIT NONE
- REAL :: x1,x2,x3,x4,x5
-
- RTable%dy = Kin*((30.0d0*RTable%w_ref/pi)-(30.0d0*x3/pi))
-
- end subroutine
|