Hello,
In order to add the initial value outputs in the Type 164 code, I prefer to create a new type and not modify the existed one in Trnsys Library.
For that I created a new component using Trnsys 17. I had some difficulties because it’s not the same code writing from defining inputs, outputs and parameters to storage; I managed to copy the code line that I am interested in but the problem remains with the storage array.
In fact when I created the new component (from Trnsys), I didn’t notice any place where I can specify my number of storage (Which is equal to 2 in Type 164).
Do I set my storage number there: ‘’Call SetNumberStoredVariables(0,0)’
I have to include (in my new component ''type210'') the storage array in FOUR places just like in type 164a:
POST CONVERGENCE MANIPULAITIONS
CALL getStorageVars(STORED,NS,INFO)
STORED(1)=STORED(2)
CALL setStorageVars(STORED,NS,INFO)
PERFORM FIRST CALL MANIPULATIONS
CALL setStorageSize(NS,INFO)
PERFORM INITIAL TIMESTEP MANIPULATIONS
STORED(1:NS) = N_INI !NO. OF MOLES IN PREVIOUS TIME STEP
CALL setStorageVars(STORED,NS,INFO)
UPDATE STORAGE
STORED(2) = NGAS
CALL setStorageVars(STORED,NS,INFO)
Are these nomenclatures work in the Type210 created by Trnsys 17? Or I have to include other nomenclatures ? such as getStaticArrayValue ? and for the others ?
Thank you in advance for your support.
Ghady DIB
Doctorant
Laboratoire CETHIL UMR 5008 Groupe Energétique des Systèmes Thermiques et Frigorifiques (ESTF) Département Génie Energétique et Environnement INSA Lyon France
SUBROUTINE TYPE164(TIME,XIN,OUT,T,DTDT,PAR,INFO,ICNTRL,*) C********************************************************************************************** C ØYSTEIN ULLEBERG * C IFE * C * C TYPE164: PRESSURIZED GAS STORAGE TANK - Version 5.0 * C * C Versions: * C (1) 1997.10.01 - Original version, documented & verified in /3/ * C (2) 2000.09.02 - Adapted for TRNWIN 14.2 W/IISiBAT 2.0, ØU * C (3) 2001.07.26 - Adapted for TRNWIN 15.0 W/IISiBAT 3.0. ØU * C (4) 2003.03.30 - New format for Error & Warning statements * C Clean-up of source code (old code removed) * C (5) 2004.08.18 - Adapted for TRNSYS 16.0 * C * C * C THIS SUBROUTINE MODELS A PRESSURIZED GAS STORAGE TANK. * C * C THE MODEL HAS TWO MODES OF OPERATION: * C * C 1. IDEAL GAS * C * C P*V = n*R*T * C * C * C 2. REAL GAS (VAN DER WAALS) * C * C * C n*R*T n^2 * C P = ----- - a * --- * C V-n*b V^2 * C * C where: * C 27*R^2*Tcr^2 * C a = ------------, constant for pressure correction * C 64*Pcr * C * C R*Tcr * C b = ----- * C 8*Pcr * C * C * C REFERENCES: * C 1. CENGEL YA, BOLES MA (1989) THERMODYNAMIS: AN ENGINEERING * C APPROACH. McGRAW-HILL BOOK COMPANY. LONDON * C 2. GRIESSHABER W, SICK F (1990) SIMULATON OF H2-02 SYSTEMS WITH * C PV FOR THE SELF-SUFFICIENT SOLAR HOUSE (GERMAN). DEPARTMENT * C OF SYSTEMS ENGINEERING/SIMULATION, FRAUNHOFER-INSTITUTE FOR * C SOLAR ENERGY SYSTEMS, GERMANY. * C 3. ULLEBERG O (1998) STAND-ALONE POWER SYSTEMS FOR THE FUTURE: * C OPTIMAL DESIGN, OPERATION & CONTROL OF SOLAR-HYDROGEN ENERGY * C SYSTEMS, PHD DISSERTATION. NORWEGIAN UNIVERSITY OF SCIENCE * C AND TECHNOLOGY, TRONDHEIM. ISBN 82-471-0344-3 * C 4. AYLWARD G, FINDLAY T (1994) SI CHEMICAL DATA. THIRD EDITION. * C JOHN WILEY & SONS, SYDNEY, AUSTRALIA. * C * C DATA: * C RGAS UNIVERSAL GAS CONSTANT [J/K-mol] * C * C PARAMETERS - TRNSYS DECK: * C 1. PMODE PRESSURE MODE (1=IDEAL GAS, 2=REAL GAS) * C 2. PMAX RATED PRESSURE FOR STORAGE VESSEL [bar] * C 3. VOL VOLUME OF STORAGE VESSEL [m3] * C 4. MOL MOLAR WEIGHT OF GAS [g/mol] * C IF PMODE=2 THEN: * C 5. TCR CRITICAL TEMPERATURE OF GAS [C] (PMODE=2) * C 6. PCR CRITICAL PRESSURE OF GAS [bar] (PMODE=2) * C * C PARAMETERS - OTHER: * C AA VAN DER WAALS CONSTANT OF GAS [Nm4/mol2] * C BB VAN DER WAALS CONSTANT OF GAS [m3/mol] * C TREF TEMPERATURE AT STANDARD CONDITIONS [C] * C PREF PRESSURE AT STANDARD CONDITIONS [bar] * C RHO_REF DENSITY OF IDEAL GAS AT STANDARD CONDITIONS [mol/m3] * C * C INPUTS: * C 1. VDOT_IN VOLUMETRIC FLOW RATE INTO TANK [Nm3/hr] * C 2. VDOT_OUT VOLUMETRIC FLOW RATE OUT OF TANK [Nm3/hr] * C 3. TGAS TEMERATURE OF GAS IN TANK [C] * C 4. PLEV_INI INITIAL PRESSURE LEVEL [0-1] (FIRST CALL ONLY) * C * C VARIABLES: * C NGAS NUMBER OF MOLES OG GAS IN TANK[mol] (FIRST CALL ONLY) * * C * C OUTPUTS: * C 1. VGAS VOLUME OF GAS STORED IN TANK (AT REF CONDS.) [Nm3] * C 2. PGAS PRESSURE OF GAS IN TANK [bar] * C 3. PLEV PRESSURE LEVEL [0-1] (0=EMPTY, 1=FULL) * C 4. VDOTDUMP VOLUMETRIC FLOW RATE OF GAS DUMPED OR VENTED OUT OF * C TANK THROUGH SAFETY VALVE [Nm3/hr] * C * C SUBSCRIPTS: * C INI INITIAL (USED FIRST CALL ONLY) * C * C********************************************************************************************** !export this subroutine for its use in external DLLs. !DEC$ATTRIBUTES DLLEXPORT :: TYPE164 C USE STATEMENTS USE TrnsysFunctions USE TrnsysConstants IMPLICIT NONE !force explicit declaration of local variables C TRNSYS DECLARATIONS DOUBLE PRECISION XIN,OUT,TIME,PAR,T,DTDT,STORED INTEGER*4 INFO(15),NPMAX,NI,NO,ND,NS,IUNIT,ITYPE,ICNTRL CHARACTER*3 OCHECK,YCHECK C SET THE MAXIMUM NUMBER OF PARAMETERS(NP),INPUTS(NIMAX),OUTPUTS(NO),AND DERIVATIVES(ND) C THAT MAY BE SUPPLIED FOR THIS TYPE PARAMETER (NPMAX=6,NI=4,NO=4,ND=0,NS=2) C REQUIRED TRNSYS DIMENSIONS DIMENSION XIN(NI),OUT(NO),PAR(NPMAX),YCHECK(NI),OCHECK(NO), & STORED(NS) C COMMON BLOCKS !none required by this Type C LOCAL VARIABLE DECLARATIONS CHARACTER (len=12) PGASStr,PMAXStr,PLEVStr,PMINStr CHARACTER (len=maxMessageLength) T164Msg DOUBLE PRECISION RGAS,PMAX,VOL,MOL,TCR,PCR,AA,BB,PREF,TREF,RHO_REF DOUBLE PRECISION TGAS,PLEV_INI,VDOT_IN,VDOT_OUT,VDOTDUMP DOUBLE PRECISION P_INI,N_INI,NDOT_IN,NDOT_OUT,NGAS,NDOTDUMP DOUBLE PRECISION VGAS,PGAS,PLEV,PMIN,TIME0,DELT INTEGER*4 PMODE,DUMP,LUW,NP INTEGER*4 IS,INIT,FINAL INTEGER IDBGUNT1,TDEBUG1,TDEBUG2,IDBGUNT2,TDEBUG3,TDEBUG4, 1 TDEBUG5,TDEBUG6 C DATA STATEMENTS DATA IUNIT/0/ DATA RGAS/8.3145/, TREF/0/, PREF/1.01325/ PMIN/0/ DATA IDBGUNT1/21/,TDEBUG1/-2/,TDEBUG2/-1/,IDBGUNT2/22/,TDEBUG3/-2/, 1 TDEBUG4/-1/,TDEBUG5/-2/,TDEBUG6/-1/ DATA YCHECK/'SF1','SF1','TE1','DM1'/ DATA OCHECK/'SF1','PR1','DM1','SF1'/ C-------------------------------------------------------------------------------------------------- C GET GLOBAL TRNSYS SIMULATION VARIABLES TIME0 = getSimulationStartTime() DELT = getSimulationTimeStep() LUW = getListingFileLogicalUnit() C-------------------------------------------------------------------------------------------------- C SET THE VERSION INFORMATION FOR TRNSYS IF(INFO(7).EQ.-2) THEN INFO(12)=16 RETURN 1 ENDIF C-------------------------------------------------------------------------------------------------- C PERFORM LAST CALL MANIPULATIONS IF (INFO(8).EQ.-1) THEN RETURN 1 ENDIF C-------------------------------------------------------------------------------------------------- C PERFORM POST CONVERGENCE MANIPULATIONS IF(INFO(13).GT.0) THEN CALL getStorageVars(STORED,NS,INFO) STORED(1)=STORED(2) CALL setStorageVars(STORED,NS,INFO) RETURN 1 ENDIF C-------------------------------------------------------------------------------------------------- C PERFORM FIRST CALL MANIPULATIONS IF (INFO(7).EQ.-1) THEN !retrieve unit and type number for this component from the INFO array IUNIT=INFO(1) ITYPE=INFO(2) !reserve space in the OUT array using INFO(6) INFO(6) = NO !set the way in which this component is to be called INFO(9) = 1 !set required number of spots in the single precision storage structure INFO(10) = 0 !reserve required number of spots in the double precision storage structure CALL setStorageSize(NS,INFO) !check that the number of parameters supplied corresponds to the model mode PMODE = JFIX(PAR(1)+0.1d0) IF (PMODE .EQ. 1) THEN NP = 4 ELSEIF (PMODE .EQ. 2) THEN NP = 6 ELSE CALL TYPECK(-4,INFO,0,1,0) ENDIF !call the type check routine to compare what this type requires to what is in the input file CALL TYPECK(1,INFO,NI,NP,ND) !call the input-output check subroutine to set the correct input and output units. CALL RCHECK(INFO,YCHECK,OCHECK) !RETURN TO THE CALLING PROGRAM RETURN 1 ENDIF C-------------------------------------------------------------------------------------------------- C PERFORM INITIAL TIMESTEP MANIPULATIONS IF (TIME.LT.(TIME0+DELT/2.)) THEN !set the UNIT number for future calls IUNIT=INFO(1) ITYPE=INFO(2) !read the parameter values and calculate the initial number of moles of gas in the tank. PMODE = JFIX(PAR(1)+0.1) PMAX = PAR(2) VOL = PAR(3) MOL = PAR(4) TGAS = XIN(3)+273.15 !C -> K PLEV_INI = XIN(4) P_INI = PLEV_INI*PMAX*1E5 !1 bar = 1E5 Pa IF (PMODE .EQ. 1) THEN NP = 4 N_INI=(P_INI*VOL)/(RGAS*TGAS) ELSEIF (PMODE .EQ. 2) THEN NP = 6 TCR = PAR(5)+273.15 !C -> K PCR = PAR(6)*1E5 !bar -> Pa !calculate initial level in tank (P_INI -> N_INI) CALL NMOL(TCR,PCR,RGAS,P_INI,VOL,TGAS,N_INI) ENDIF !check the parameters for problems and RETURN if any are found !REVISIT: not handled yet. !set initial values of the global storage array variables STORED(1:NS) = N_INI !NO. OF MOLES IN PREVIOUS TIME STEP CALL setStorageVars(STORED,NS,INFO) !set initial output values OUT(1:NO)=0.d0 RETURN 1 ENDIF C-------------------------------------------------------------------- C THIS IS AN ITERATIVE CALL TO THIS COMPONENT *** C-------------------------------------------------------------------- C RE-READ THE PARAMETERS IF ANOTHER UNIT OF THIS TYPE HAS BEEN CALLED SINCE THE LAST C TIME THEY WERE READ IN IF(INFO(1).NE.IUNIT) THEN IUNIT = INFO(1) ITYPE = INFO(2) !reread parameter values (those contained in TRNSYS input file) PMODE = JFIX(PAR(1)+0.1) PMAX = PAR(2) VOL = PAR(3) MOL = PAR(4) IF (PMODE .EQ. 1) THEN NP = 4 ELSEIF (PMODE .EQ. 2) THEN NP = 6 TCR = PAR(5)+273.15 !C -> K PCR = PAR(6)*1E5 !bar -> Pa ENDIF ENDIF C RETRIEVE VALUES FROM STORAGE CALL getStorageVars(STORED,NS,INFO) C SET INPUTS VDOT_IN = XIN(1) VDOT_OUT = XIN(2) TGAS = XIN(3)+273.15 C---CALCULATION OF NEW STORAGE LEVEL--- C DENSITY OF GAS AT REFERENCE CONDITIONS RHO_REF = PREF*1E5/(RGAS*(TREF+273.15)) !1 bar = 1E5 Pa C MOLES DUMP = 0 45 CONTINUE NDOT_IN = VDOT_IN*RHO_REF NDOT_OUT = VDOT_OUT*RHO_REF IF (DUMP.EQ.0) THEN NDOTDUMP = 0 VDOTDUMP = 0 ELSE !REVISIT: simply dumping the inlet flow of gas may not always be enough in order to get the pressure !down to its maximum allowable level. DB added a first cut fix which he wasn't too pleased with to !a version of this Type. It is not included here but this issue ought to be addressed. NDOTDUMP = NDOT_IN VDOTDUMP = VDOT_IN ENDIF NGAS = STORED(1) + (NDOT_IN-NDOT_OUT-NDOTDUMP)*DELT C VOLUME OF GAS AT REFERENCE CONDITIONS VGAS = NGAS/RHO_REF C PRESSURE IF (PMODE.EQ.1) THEN PGAS = NGAS*RGAS*TGAS/VOL ELSEIF (PMODE.EQ.2) THEN AA = (27*RGAS**2*TCR**2)/(64*PCR) BB = (RGAS*TCR)/(8*PCR) PGAS = (NGAS*RGAS*TGAS)/(VOL-NGAS*BB)-AA*(NGAS/VOL)**2 ENDIF C---FINAL CALCULATIONS & CHECKS--- PLEV = PGAS/(PMAX*1E5) !1 bar = 1E5 Pa PGAS = PGAS/1E5 !1 bar = 1E5 Pa C DUMP GAS IF PRESSURE IS TOO HIGH C (CONTINUE SIMULATION, BUT ISSUE WARNING) IF(PLEV.GE.1.0) THEN WRITE (PGASStr,*) JFIX(PGAS+0.1d0) WRITE (PMAXStr,*) JFIX(PMAX+0.1d0) T164Msg = 'The gas storage pressure ('//TRIM(ADJUSTL(PGASStr 1))//' [bar]) is too high. The maximum allowable gas pressure is ' 1//TRIM(ADJUSTL(PMAXStr))//' [bar]. Excess gas was dumped.' CALL MESSAGES(-1,T164Msg,'notice',IUNIT,ITYPE) PGAS = PMAX*1E5 DUMP = 1 !(1=YES,0=NO) GOTO 45 ELSE DUMP = 0 ENDIF C STOP SIMULATION IF PRESSURE IS TOO LOW IF(PLEV.LE.0) THEN WRITE (PLEVStr,*) JFIX(PLEV+0.1d0) WRITE (PMINStr,*) JFIX(PMIN+0.1d0) T164Msg = 'The gas storage pressure ('//TRIM(ADJUSTL(PLEVStr 1))//' [bar]) is too low. The minimum allowable gas pressure is ' 1//TRIM(ADJUSTL(PMINStr))//' [bar]. ' CALL MESSAGES(-1,T164Msg,'fatal',IUNIT,ITYPE) IF ( ErrorFound() ) RETURN 1 ENDIF C UPDATE STORAGE STORED(2) = NGAS CALL setStorageVars(STORED,NS,INFO) C PRINT DEBUGGING INFORMATION TO THE LIST FILE IF NECESSARY. IF((INFO(1).EQ.IDBGUNT1) & .AND.((TIME.GE.TDEBUG1).AND.(TIME.LE.TDEBUG2))) THEN WRITE(LUW,*) 'UNIT = ',INFO(1) WRITE(LUW,*) 'TIME = ',TIME WRITE(LUW,*) 'ITER = ',INFO(7) WRITE(LUW,*) 'VDOT_IN = ',VDOT_IN WRITE(LUW,*) 'VDOT_OUT = ',VDOT_OUT WRITE(LUW,*) 'VDOTDUMP = ',VDOTDUMP WRITE(LUW,*) ' ' ENDIF IF((INFO(1).EQ.IDBGUNT2) & .AND.((TIME.GE.TDEBUG3).AND.(TIME.LE.TDEBUG4))) THEN WRITE(LUW,*) 'UNIT = ',INFO(1) WRITE(LUW,*) 'TIME = ',TIME WRITE(LUW,*) 'ITER = ',INFO(7) WRITE(LUW,*) 'VDOT_IN = ',VDOT_IN WRITE(LUW,*) 'VDOT_OUT = ',VDOT_OUT WRITE(LUW,*) ' ' ENDIF IF((INFO(1).EQ.IDBGUNT1) & .AND.((TIME.GE.TDEBUG5).AND.(TIME.LE.TDEBUG6))) THEN WRITE(LUW,*) 'UNIT = ',INFO(1) WRITE(LUW,*) 'TIME = ',TIME WRITE(LUW,*) 'ITER = ',INFO(7) WRITE(LUW,*) 'VDOT_IN = ',VDOT_IN WRITE(LUW,*) 'VDOT_OUT = ',VDOT_OUT WRITE(LUW,*) ' ' ENDIF C---OUTPUTS--- OUT(1) = VGAS OUT(2) = PGAS OUT(3) = PLEV OUT(4) = VDOTDUMP RETURN 1 END C---END OF GAS STORAGE SUBROUTINE C---ONLY SUBROUTINES & FUNCTIONS BEYOND THIS POINT--- SUBROUTINE NMOL(TCR,PCR,RGAS,P,V,T,N) C*********************************************************************** C * C THIS SUBROUTINE USES THE NEWTON-RAPHSON METHOD ON THE * C VAN DER WAALS EQUATION FOR REAL GASES. * C * C INPUTS: * C TCR CRITICAL TEMPERATURE OF GAS [C] * C PCR CRITICAL TEMPERATURE OF GAS [Pa] * C RGAS UNIVERSAL GAS CONSTANT [J/K-mol] * C P PRESSURE [bar] * C V VOLUME [m3] * C T TEMERATURE OF [K] * C * C OUTPUTS: * C N MOLES OF GAS [mol] * C * C OTHER: * C AA VAN DER WAALS CONSTANT OF GAS [Nm4/mol2] * C BB VAN DER WAALS CONSTANT OF GAS [m3/mol] * C FUN FUN = F(N,P) = 0 VAN DER WAALS EQUATION * C DER DER = dF(N,P)/dN DERIVATIVE OF V.D.W. wrt N * C EPS TERMINATION CRITERIA * C ERR RELATIVE ERROR * C * C*********************************************************************** DOUBLE PRECISION TCR,PCR,RGAS,P,V,T,N DOUBLE PRECISION AA,BB,FUN,DER,N0,EPS,ERR PARAMETER (EPS=0.001) C CALCULATION OF REAL GAS COEFFICEINTS AA = (27*RGAS**2*TCR**2)/(64*PCR) BB = (RGAS*TCR)/(8*PCR) C START VALUE FROM IDEAL GAS LAW N = (P*V)/(RGAS*T) 100 N0 = N FUN = AA*BB*N**3-AA*V*N**2+(BB*P*V**2+RGAS*T*V**2)*N-P*V**3 DER = 3*AA*BB*N**2-2*AA*V*N+(BB*P*V**2+RGAS*T*V**2) N = N-FUN/DER ERR = DABS((N-N0)/N0) IF (ERR.GT.EPS) GOTO 100 RETURN END
Subroutine Type210 ! Object: Reservoir ! Simulation Studio Model: Type210 ! ! Author: ! Editor: ! Date: November 10, 2017 ! last modified: November 10, 2017 ! ! ! *** ! *** Model Parameters ! *** ! PMODE - [-Inf;+Inf] ! PMAX - [-Inf;+Inf] ! VOL - [-Inf;+Inf] ! MOL - [-Inf;+Inf] ! *** ! *** Model Inputs ! *** ! VDOT_IN - [-Inf;+Inf] ! VDOT_OUT - [-Inf;+Inf] ! TGAS - [-Inf;+Inf] ! PLEV_INI - [-Inf;+Inf] ! *** ! *** Model Outputs ! *** ! VGAS - [-Inf;+Inf] ! PGAS - [-Inf;+Inf] ! PLEV - [-Inf;+Inf] ! VDOTDUMP - [-Inf;+Inf] ! *** ! *** Model Derivatives ! *** ! (Comments and routine interface generated by TRNSYS Studio) !************************************************************************ !----------------------------------------------------------------------------------------------------------------------- ! This TRNSYS component skeleton was generated from the TRNSYS studio based on the user-supplied parameters, inputs, ! outputs, and derivatives. The user should check the component formulation carefully and add the content to transform ! the parameters, inputs and derivatives into outputs. Remember, outputs should be the average value over the timestep ! and not the value at the end of the timestep; although in many models these are exactly the same values. Refer to ! existing types for examples of using advanced features inside the model (Formats, Labels etc.) !----------------------------------------------------------------------------------------------------------------------- Use TrnsysConstants Use TrnsysFunctions !----------------------------------------------------------------------------------------------------------------------- !DEC$Attributes DLLexport :: Type210 !----------------------------------------------------------------------------------------------------------------------- !Trnsys Declarations Implicit None Double Precision Timestep,Time Integer CurrentUnit,CurrentType ! PARAMETERS DOUBLE PRECISION PMODE DOUBLE PRECISION PMAX DOUBLE PRECISION VOL DOUBLE PRECISION MOL ! INPUTS DOUBLE PRECISION VDOT_IN DOUBLE PRECISION VDOT_OUT DOUBLE PRECISION TGAS DOUBLE PRECISION PLEV_INI ! LOCAL VARIABLE DECLARATIONS DOUBLE PRECISION RGAS,PMAX,VOL,MOL,TCR,PCR,AA,BB,PREF,TREF,RHO_REF DOUBLE PRECISION TGAS,PLEV_INI,VDOT_IN,VDOT_OUT,VDOTDUMP DOUBLE PRECISION P_INI,N_INI,NDOT_IN,NDOT_OUT,NGAS,NDOTDUMP DOUBLE PRECISION VGAS,PGAS,PLEV,PMIN,TIME0,DELT INTEGER*4 PMODE,DUMP,LUW,NP INTEGER*4 IS,INIT,FINAL ! DATA STATEMENTS DATA IUNIT/0/ DATA RGAS/8.3145/, TREF/0/, PREF/1.01325/ PMIN/0/ !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Get the Global Trnsys Simulation Variables Time=getSimulationTime() Timestep=getSimulationTimeStep() CurrentUnit = getCurrentUnit() CurrentType = getCurrentType() !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Set the Version Number for This Type If(getIsVersionSigningTime()) Then Call SetTypeVersion(17) Return EndIf !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Do Any Last Call Manipulations Here If(getIsLastCallofSimulation()) Then Return EndIf !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Perform Any "After Convergence" Manipulations That May Be Required at the End of Each Timestep If(getIsConvergenceReached()) Then Return EndIf !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Do All of the "Very First Call of the Simulation Manipulations" Here If(getIsFirstCallofSimulation()) Then !Tell the TRNSYS Engine How This Type Works Call SetNumberofParameters(4) !The number of parameters that the the model wants Call SetNumberofInputs(4) !The number of inputs that the the model wants Call SetNumberofDerivatives(0) !The number of derivatives that the the model wants Call SetNumberofOutputs(4) !The number of outputs that the the model produces Call SetIterationMode(1) !An indicator for the iteration mode (default=1). Refer to section 8.4.3.5 of the documentation for more details. Call SetNumberStoredVariables(0,0) !The number of static variables that the model wants stored in the global storage array and the number of dynamic variables that the model wants stored in the global storage array Call SetNumberofDiscreteControls(0) !The number of discrete control functions set by this model (a value greater than zero requires the user to use Solver 1: Powell's method) Return EndIf !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Do All of the First Timestep Manipulations Here - There Are No Iterations at the Intial Time If (getIsFirstTimestep()) Then PMODE = getParameterValue(1) PMAX = getParameterValue(2) VOL = getParameterValue(3) MOL = getParameterValue(4) VDOT_IN = GetInputValue(1) VDOT_OUT = GetInputValue(2) TGAS = GetInputValue(3)+273.15 PLEV_INI = GetInputValue(4) P_INI = PLEV_INI*PMAX*1E5 !1 bar = 1E5 Pa N_INI=(P_INI*VOL)/(RGAS*TGAS) !Check the Parameters for Problems (#,ErrorType,Text) !Sample Code: If( PAR1 <= 0.) Call FoundBadParameter(1,'Fatal','The first parameter provided to this model is not acceptable.') !Set the Initial Values of the Outputs (#,Value) Call SetOutputValue(1, 0) ! VGAS Call SetOutputValue(2, 13) ! PGAS Call SetOutputValue(3, 0) ! PLEV Call SetOutputValue(4, 0) ! VDOTDUMP !If Needed, Set the Initial Values of the Static Storage Variables (#,Value) !Sample Code: SetStaticArrayValue(1,0.d0) SetStaticArrayValue(1,) !If Needed, Set the Initial Values of the Dynamic Storage Variables (#,Value) !Sample Code: Call SetDynamicArrayValueThisIteration(1,20.d0) !If Needed, Set the Initial Values of the Discrete Controllers (#,Value) !Sample Code for Controller 1 Set to Off: Call SetDesiredDiscreteControlState(1,0) Return EndIf !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !ReRead the Parameters if Another Unit of This Type Has Been Called Last If(getIsReReadParameters()) Then !Read in the Values of the Parameters from the Input File PMODE = getParameterValue(1) PMAX = getParameterValue(2) VOL = getParameterValue(3) MOL = getParameterValue(4) EndIf !----------------------------------------------------------------------------------------------------------------------- !Read the Inputs VDOT_IN = GetInputValue(1) VDOT_OUT = GetInputValue(2) TGAS = GetInputValue(3)+273.15 PLEV_INI = GetInputValue(4) !Check the Inputs for Problems (#,ErrorType,Text) !Sample Code: If( IN1 <= 0.) Call FoundBadInput(1,'Fatal','The first input provided to this model is not acceptable.') If(ErrorFound()) Return !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- ! *** PERFORM ALL THE CALCULATION HERE FOR THIS MODEL. *** !----------------------------------------------------------------------------------------------------------------------- !---CALCULATION OF NEW STORAGE LEVEL--- ! DENSITY OF GAS AT REFERENCE CONDITIONS RHO_REF = PREF*1E5/(RGAS*(TREF+273.15)) !1 bar = 1E5 Pa ! MOLES NDOT_IN = VDOT_IN*RHO_REF NDOT_OUT = VDOT_OUT*RHO_REF NGAS = STORED(1) + (NDOT_IN-NDOT_OUT-NDOTDUMP)*DELT ! VOLUME OF GAS AT REFERENCE CONDITIONS VGAS = NGAS/RHO_REF ! PRESSURE PGAS = NGAS*RGAS*TGAS/VOL !---FINAL CALCULATIONS & CHECKS--- PLEV = PGAS/(PMAX*1E5) !1 bar = 1E5 Pa PGAS = PGAS/1E5 !1 bar = 1E5 Pa !----------------------------------------------------------------------------------------------------------------------- !If Needed, Get the Previous Control States if Discrete Controllers are Being Used (#) !Sample Code: CONTROL_LAST=getPreviousControlState(1) !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !If Needed, Get the Values from the Global Storage Array for the Static Variables (#) !Sample Code: STATIC1=getStaticArrayValue(1) !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !If Needed, Get the Initial Values of the Dynamic Variables from the Global Storage Array (#) !Sample Code: T_INITIAL_1=getDynamicArrayValueLastTimestep(1) !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Perform All of the Calculations Here to Set the Outputs from the Model Based on the Inputs !Sample Code: OUT1=IN1+PAR1 !If the model requires the solution of numerical derivatives, set these derivatives and get the current solution !Sample Code: T1=getNumericalSolution(1) !Sample Code: T2=getNumericalSolution(2) !Sample Code: DTDT1=3.*T2+7.*T1-15. !Sample Code: DTDT2=-2.*T1+11.*T2+21. !Sample Code: Call SetNumericalDerivative(1,DTDT1) !Sample Code: Call SetNumericalDerivative(2,DTDT2) !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !Set the Outputs from this Model (#,Value) Call SetOutputValue(1, 0) ! VGAS Call SetOutputValue(2, 0) ! PGAS Call SetOutputValue(3, 0) ! PLEV Call SetOutputValue(4, 0) ! VDOTDUMP !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !If Needed, Store the Desired Disceret Control Signal Values for this Iteration (#,State) !Sample Code: Call SetDesiredDiscreteControlState(1,1) !----------------------------------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------------------------------- !If Needed, Store the Final value of the Dynamic Variables in the Global Storage Array (#,Value) !Sample Code: Call SetValueThisIteration(1,T_FINAL_1) !----------------------------------------------------------------------------------------------------------------------- Return End !-----------------------------------------------------------------------------------------------------------------------