You are on page 1of 51

®

ProMax
Advanced Training:
Visual Basic
for Applications

Bryan Research & Engineering, Inc.


Chemical Engineering Consultants

P.O. Box 4747 • Bryan, Texas 77805


Office 979-776-5220 • Fax 979-776-4818
E-mail sales@bre.com or support@bre.com
ii
Table of Contents

ProMax® Level II—Visual Basic for Applications Agenda .............................................. iv


Why use Visual Basic for Applications (VBA) with ProMax? .......................................... 1
Object Oriented Programming (OOP) Paradigm and Object Definition ............................ 2
Simplified Drawing Program Object Model ................................................................... 3
Object Property and Method Functions .......................................................................... 3
Object Identity ................................................................................................................ 4
Excerpt of an Pump Object in ProMax ........................................................................... 4
Excerpt of Pump Object in ProMax Showing Event Callback ....................................... 5
Visual Basic for Applications (VBA) ................................................................................. 6
Tools for use in Visual Basic for Applications Development ........................................ 6
Declaring Variables in Visual Basic for Applications .................................................... 7
Common Keywords and Operators in Visual Basic for Applications ............................ 8
Common Expressions in Visual Basic for Applications ................................................. 9
Creating a Simple Hello World Program in VBA ........................................................ 11
Setting a Cell in Excel .................................................................................................. 11
Fill a Range of Cells in Excel ....................................................................................... 12
Using Objects as Variables ........................................................................................... 12
Tools for Debugging VBA Projects.............................................................................. 13
Commonly Used ProMax Objects .................................................................................... 14
Exercises Using VBA ....................................................................................................... 17
Exercise 1: Listing all PStream names in a Project ...................................................... 17
Exercise 2: Listing all Component names in All Environments in a Project ............... 18
Exercise 3: List the Names of all Components used in a Flowsheet Environment ...... 18
Exercise 4: Units Conversion using the PDouble Object ............................................. 19
Exercise 5: Generate Saturated Steam Properties Using NBS Steam Tables Package 20
Exercise 6: Tabulate in Excel the Effect of TEG Circulation Rate on Water Content . 22
Exercise 7: Compute the Bubble and Dew Point Temperatures of a Binary System ... 23
Appendices ........................................................................................................................ 25

iii
ProMax® Level II—Visual Basic for Applications Agenda
Day 1 ProMax and VBA

Introduction to Object Oriented Programming


Object Properties and Methods
Object Identities

Visual Basic for Applications (VBA)


Tools available in VBA
Common Keywords, Operators and Expressions in VBA
Using Objects and Variables
Tools for Debugging

Common ProMax Objects

VBA Exercises
Recording Macros in Excel
Using ProMax Objects in Excel
Using ProMax Objects in Visio

iv
Why use Visual Basic for Applications (VBA) with
ProMax?
Provides access to information that my not be readily available in the user interface
o Pure component properties
o Thermodynamic properties such as fugacity coefficients and activity
coefficients
Allows authoring of custom calculations based on data in ProMax at a higher level
than user values
Can be used to transfer information from ProMax to other applications such as
Microsoft Excel or Visio
Create routines to perform often needed tasks
Allows access to unit conversion engine within ProMax
ProMax property stencils are written in VBA

1
Object Oriented Programming (OOP) Paradigm
and Object Definition
OOP paradigm is the common framework for virtually every major modern
software product
OOP is not part of typical engineering academic preparation
Understanding is more a conceptual problem than mechanical problem due to
training in procedural programming
An object presents an individual, identifiable item, unit, or entity, either real or abstract
with a well-defined role in the problem domain
Tangible or physical objects
o Pump, compressor, page, shape, cell
Abstract objects
o Thermodynamic and physical property calculation engines
Three basic features of an object
o State
o Behavior
o Identity
Application that hosts the objects is typically called the server and the application
that access the objects is typically called the client
Client accesses the objects in the server through an exposed interface
The interface exposes properties and methods to clients where they monitor or
manipulate the state and behavior of an object
Many objects are solely collections of other objects and are usually named with a
plural noun
Objects within collections usually are the singular of the same noun
OOP programs have parent-child hierarchy with objects representing features
present in program

2
Simplified Drawing Program Object Model

Pages Shapes

Drawing
Page Shape
Font

Drawing Page Shape Font


(P) Pages (P) Width (P) Type (P) TypeFace
(P) Height (P) Color (P) Color
...
(P) Shapes (P) X (P) Size
(M) Delete (P) Y (P) Bold
(P) Italic
... (P) Width
Key: (P) Underline
(P) Height
Collection ...
(P) Font

Object (M) Rotate


(M) Shift
(M) Delete
P: Property
...
M: Method

Object Property and Method Functions


Properties
o Allow retrieval and manipulation of the state of the object
o Frequently provide access to other objects in hierarchy or simple values
Methods
o Usually cause some type of action or computation to occur
Both can require function arguments
Occasionally no clear distinction between properties and methods

3
Object Identity
Identifies one object from another
Not limited to identification between two of the same types of objects
Not limited to objects running in the same process
Usually done by comparing memory addresses of objects
Different memory addresses—different objects

Excerpt of an Pump Object in ProMax

(P) Name

Block (P) Status

(M) Solve

...

Pump (P) Curves

Pump Object

Above figure shows simplified excerpt of Pump block in ProMax


Symbol used to denote an interface for external client connection
Arguments for properties and methods omitted from drawing for simplicity
Block interface is an abstract interface used by all blocks in ProMax that provides
framework common to all blocks. All unit operations have a Name and Status
property in addition to a Solve method.
Pump interface is specific to pump and contains properties and methods specific to
the pump (performance curves)
Implementation of the pump state, behavior, and identify are encapsulated within
boundary of the pump, hidden from client. Encapsulation provides all data
(variables) and routines (code) required to implement public state exposed through
the interfaces.
Frequently interfaces inherit or derive from one another. Access to properties and
methods base interfaces are available in more derived interfaces.

4
Excerpt of Pump Object in ProMax Showing Event
Callback

BlockEvents
(M) BlockStatusChanged
(P) Name

... Block (P) Status

(M) Solve

...

Pump (P) Curves

End User Defined


Client Pump Object

Callback interfaces allow pump to communicate with its client when certain events
occur that are not a direct result of the client’s actions
Callback interfaces are sometimes called event interfaces
Event methods are defined by the object implementation (e.g., ProMax) but the
interface itself is implemented in the client (e.g., your client application). For this
case, the client implements a method called BlockStatusChanged
Client must be an object oriented programming language so it can implement the
interface
Event interfaces are supported in VBA using the WithEvents keyword

5
Visual Basic for Applications (VBA)
Macro programming language available in most Microsoft Office Applications, e.g.,
Word, Excel, Visio, Access, etc.
Syntactically based on Microsoft Visual Basic
VBA facilitates the use of OOP but does not require it—user must determine when
and when not to use OOP
Can create custom objects in VBA for use in an application
VBA provides access to objects in OOP programs such as Excel, Visio, and
ProMax
Macro recorder available in some applications (e.g., Excel and Visio) to assist in
building macros and learning object hierarchy
Syntax is relatively simple and case insensitive
Powerful set of intrinsic functions for math, string manipulation and processing, etc.
IntelliSense capabilities that allow the VBE code editor to assist the developer in
selecting options available as code is being typed

Tools for use in Visual Basic for Applications


Development
Extensive language reference available in all Microsoft Office products
o Full reference for keywords, statements, functions
o Location to find intrinsic functions
Object Browser
o Important tool for use with OOP applications
o Accessed by pressing F2 in the VBE or from the View menu
o Provides access to data in type libraries currently referenced by VBA—use
Tools->References menu item to add more type library references (e.g.,
BR&E ProMax)
o Once type library loaded, allows viewing of all properties and methods
exposed to external clients in the type library
o Objects in the host application will automatically appear in the object
browser as the type libraries for those applications are automatically added
to the reference list
o Can copy/paste data from Object Browser to source code editor
Intellisense capabilities in the editor. Optional arguments for function and
subroutine calls are listed in [] in Intellisense. Just because a default argument is
present does not mean it is the appropriate argument for your call.
Use F1 key on any keyword to obtain further information in the online help
6
Declaring Variables in Visual Basic for Applications
Use the Dim and As keywords to declare variables
If the Option Explicit (recommended) statement is placed in the code, all
variables must be declared with the Dim statement.
Common types of variables used in VBA
o Long—defines a 4 byte integer value. Most integers passed to ProMax will
be long values.
o Integer—defines a 2 byte integer value
o Double—defines an 8 byte double precision floating point number
o Single—defines an 4 byte single precision floating point number.
ProMax exclusively utilizes double precision data.
o String—used to declare strings. VBA contains a powerful set of
functions for manipulating string variables.
o Object—object variables are memory addresses that reference objects.
Used to access properties and methods of an interface. Use the Set
statement to assign object variables. Declaring a variable with the generic
term Object gives a variable that can reference any type of object.
Declaring a variable with the specific name of the interface restricts use to
the specific type of object declared but is much more efficient and easier to
use than the generic form.
o Boolean—used to hold True/False values
o Date—used to hold date and time data
o Variant—A special type of variable that can be used to hold any type of
data. It is the union of all types of data held in a single variable. The
VarType function can be used to determine the type of data stored in a
Variant. A variant can also contain four special values: Empty, Null,
Error, or Nothing. The function IsEmpty, IsError, and IsNull
can be used to test variants for these special values.
Arrays may be declared with the dimensions or the dimensions can later be set
during execution using the ReDim statement. Arrays that are sized during
execution are declared with an empty set of parenthesis:
Dim X(0 to 5) As Double, Y() As Long

ReDim Y(N1 to N2)

In the above example, X is declared to contain 6 elements with indices ranging from
0 to 5. Memory for the Y array will be allocated during execution and the range of
indices will be from N1 to N2. If no lower range of indices is provided, VBA
assumes the lower bounds to be zero.

7
The intrinsic UBound and LBound functions can be used to determine the upper
and lower bounds of an array during execution
Local variables are declared within the context of a subroutine or function. Their
use is limited to the scope of the routine in which they are defined.
Global variables are declared outside the scope of subroutines and functions. Use
the Public keyword to mark them public to all modules in the project.
Variables declared with Const are constant values that can be used instead of
literal values (e.g., Const Pi = 3.14159265358979323). Constant values
can be declared globally or locally.
Enumerated data types are used extensively throughout VBA. Enumerated types
are Long values that are represented by a more recognizable name rather simply
using integer values. Among other uses, they are used for flags and property
values. ProMax and the Microsoft Office application use many different
enumerators to assist in VBA code writing.

Common Keywords and Operators in Visual Basic for


Applications
Dim WithEvents—used to declare an interface that will receive events as a
callback interface
Public—used in declaring variables and routines to indicate they are global in
scope and are not hidden from other modules in VBA
Private—variables and routines will only be available in the scope of the current
module
+,-,*,/,^,=
. (dot operator)—used to invoke properties and methods on objects. Requires an
object reference as the value to the left of the period.
& (ampersand)—concatenation operator. Allows strings and values to be
concatenated to form longer strings. For example:
S = "The value is " & M & " lb/hr."

would create a string that could be used to display the mass flow rate contained in
variable M.
_ (underscore)—used to split a long line of code into multiple lines. Simply type
an underscore at the end of the line to split it and continue on the next line
Is—used to compare two object references for identity
Set—used to set a declared object variable to a specific instance of the object.
Variable type must be declared the generic Object or the name of the specific
object interface.
New—used to create new instances of creatable objects in memory

8
Nothing—used in checking whether a reference variable has been initialized or
not to an object. Used with Set to release memory associated with a reference
variable
True/False—used for assignment and comparison of boolean variables
And/Or—used in creating logical And and logical Or expressions

Common Expressions in Visual Basic for Applications


Comments are created by using a single quote sign and can start anywhere on a line
Sub/End Sub—creates a subroutine or macro
Sub DisplayString(S As String)
[Exit Sub]
MsgBox S
End Sub

Function/End Function—creates a function or macro that returns a result


Function TanH(X As Double) As Double
[Exit Function]
TanH = (Exp(X) – Exp(-X)) / (Exp(X) + Exp(-X))
End Function

If Then…ElseIf…Else…End If —conditional logic flow control.


Information in brackets [] is optional.
If condition Then statements [Else statements]

Or the block form:


If condition Then
statements
[ElseIf condition Then
statements
Else
statements]
End If

For…Next statement—used for creating loops. Use Exit For to break out of
loop execution before exhausting the counter
For counter=start To end [Step increment]
statements
Exit For
statements
Next [counter]

9
While…Wend statement—alternate looping code. Uses boolean condition rather
than counter to control loop flow.
While condition
statements
Wend

Do…Loop statement—alternate looping code. More structured and powerful than


While…Wend.

Do [{While | Until} condition]


Statements
[Exit Do]
Statements
Loop

Or the following syntax:


Do
Statements
[Exit Do]
Statements
Loop [{While | Until} condition]

For Each…Next statement—provides looping through objects in a collection or


an array. Simpler to use and more efficient than a standard For…Next statement
where a counter requires maintaining.
For Each element In group
Statements
[Exit For]
Statements
Next [element]

On Error statements—provides for handling exceptions and errors that can


occur when making calls to methods and properties. There are three basic forms:
On Error GoTo line
On Error Resume Next
On Error GoTo 0

The first form indicates that if an error or exception occurs, VBA will transfer
execution to a line label line. The second form simply indicates to continue
execution on the line immediately following the line that caused the error. The
third form disables any error handling in the current procedure.

10
Creating a Simple Hello World Program in VBA
Using Tools->Macro->Visual Basic Editor (or alternatively Alt-F11), invoke the
VBE in Microsoft Excel.
Open the ThisWorkbook class module from the VBE project browser
Type the following code noting that the VBE editor will assist you in much of the
typing:
Sub HelloWorld()
MsgBox "Hello World"
End Sub

Execute the code by selecting Run->Sub/UserForm or press the F5 key


Change the MsgBox statement to Debug.Print. The Debug.Print command
invokes the Print method on the Debug object in VBA. The Debug object is an
internal object available to all VBA programs. Another internal object that is
frequently used in the Err object.
Execute the code by selecting Run->Sub/UserForm or press the F5 key. The results
now should be placed in the Immediate Window (found in the VBE View menu) of
VBE rather than a message box appearing.

Setting a Cell in Excel


Using Tools->Macro->Visual Basic Editor (or alternatively Alt-F11), invoke the
VBE in Microsoft Excel.
Open the ThisWorkbook class module from the VBE project browser
Type the following code into the VBE editor
Sub SetCell()
ThisWorkbook.Worksheets(1).Cells(1, 1).Value = 100
End Sub

ThisWorkbook is a variable that references the current workbook, the


Worksheets is a collection that holds all of the worksheets present in
ThisWorkbook, and the Cells is a collection that represents the cells of the
worksheet using row and column values as arguments. The Value property of the
cell represents its value.
The parent-child hierarchy in Excel is evident in the assignment statement
Items within a collection are obtain by using the () operator or by using the
CollectionName.Item() property. The Item() property is the default property
for most collections.
Most collections in Excel are one based, i.e., their lower index is one. Collections
in ProMax are zero based.

11
Some collections are collections of named objects. In that case, the index can be an
integer or a string. In the above example, the worksheets collection could be
accessed using syntax such as Worksheets.Item("Sheet1"). The index
argument to the property is a variant type which can hold either a long value or a
string.
Execute the code and the value of 100 should be placed into the A1 cell of Sheet1 in
the workbook
Note that the macro SetCell is now available as a macro from the Tools->Macro-
>Macros menu in the Excel Workbook

Fill a Range of Cells in Excel


Using Tools->Macro->Visual Basic Editor (or alternatively Alt-F11), invoke the
VBE in Microsoft Excel.
Open the ThisWorkbook class module from the VBE project browser
Type the following code into the VBE editor
Sub SetCells()
For J = 1 To 100
ThisWorkbook.Worksheets(1).Cells(J, 1).Value = J
Next
End Sub

Execute the code and the value from 1 through 100 should be placed in cells A1 to
A100.

Using Objects as Variables


Each time the “.” operator is invoked, a property or method is called
For efficiency, variables can be declared to hold frequently needed object
references and thus limit the number of calls that must be made
Change the previous implementation of SetCells to the following:
Sub SetCells()
Dim WS As Worksheet, R As Range

Set WS = ThisWorkbook.Worksheets("Sheet1")
For j = 1 To 100
Set R = WS.Cells(j, 1)
R.Value = j
R.Font.Size = 6
Next
End Sub

Here the Worksheet object is cached in variable WS and is only obtained once.
The cell to change is cached in the Range object variable R since multiple
operations are to be invoked on this single cell each time through the loop.

12
Use Set VariableName = Nothing to release a variable if needed
VBA provides the GetObject function which when passed a ProMax moniker
string will return the object representing the ProMax object. Not always most
efficient method for object access but sometimes quite useful. Must use an Out of
Process type moniker GetObject is called from within ProMax Visio VBA or
from Excel VBA in a ProMax OLE embedded workbook.

Tools for Debugging VBA Projects


VBE contains an internal debugger that can control flow and monitor variables
Most debugger related commands located in Debug menu
To toggle a breakpoint on a line, use the Debug->Toggle Breakpoint command,
press the F9 key, or click in the border to the left of the line. The line will be
highlighted in red.
Execution can be started and restarted using commands in the Run menu
The Debug menu contains commands to step through the code for data monitoring
Placing the mouse over variables or property functions will show results in a tooltip
The Locals window can be activated to show local variables
The Watch window can be used to display expressions for viewing
The Immediate window is used in conjunction with the Debug.Print method

13
Commonly Used ProMax Objects
ProMax
o Top level object automatically created when running in Visio
o Create with the New VBA operator outside of Visio based execution
o Provides access to the project
Project
o Represents a ProMax project
o Most objects are descendants of the Project
o Container for Environments, Flowsheets, Oils, EnergyBudgets, Recoveries,
ExcelWorkbooks, SpeciesCache, SpeciesNames
ExcelWorkbooks
o Collection containing referencing all Excel Workbooks in the project
o The Item method can be used to manipulate an Excel Workbook as it returns
a Workbook object
o From Visio, must add a reference to the Microsoft Excel Object Library to
use the workbook. Use the References Tools->References menu in the VBE
to add the reference by locating the Microsoft Excel Object Library in the
list
Environment
o Access to component list for environment
o Allows selection of property package for the environment
o Provides the default PhysProp object and allows creation of new PhysProp
objects
Species
o Obtained from the SpeciesCache collection in the Project or from the
Component objects that represent each component installed in an
environment
o Access to fundamental data in a species
 Constant properties such as molecular weight, critical constants,
acentric factor, etc.
 Variable (temperature dependent) properties such as vapor pressure,
viscosity, thermal conductivity
 Gibbs free energy and heats of formation
o Returns SpeciesName object providing information about the name of the
species including CAS registry number

14
PhysProp
o Fundamental thermodynamic calculation engine interface
o Binary data calculation
 Infinite dilution activity coefficients
 Henry’s law coefficients
o Component data calculation
 Activity coefficients
 Fugacity coefficients
 Partial molar volumes
o Interphase data calculation
 Surface tension
o Mixture data calculation (partial list below)
 Enthalpies
 Entropies
 Gibbs free energies
 Viscosities
o Pure property calculation (partial list below)
 Enthalpies
 Entropies
 Gibbs free energies
 Surface tension
o Temperature partial derivatives also available
o Can create from environment and set a limited component list for more
efficient calculation
Flowsheet
o Container for the Blocks, PStreams, and QStreams collection that belong to
the flowsheet
o Can object reference to Visio Page object
o Has property to return environment assigned to flowsheet
Block
o Access to block properties, connections, status, name, etc.
o Many blocks support multiple interfaces but all must minimally support this
interface
o Block properties index differs from each type of block
PStream
o Access to the process stream object including its phases, status, name,
connectivity, etc.
o Ability to perform flash operations
15
QStream
o Access to the energy stream object including status, name, connectivity, and
energy rate
Phase
o Contains composition and properties for phases in a process stream
o Phases collection indexed with a pmxPhaseEnum enumeration
o Properties of a phase are pmxPhasePropEnum enumerators
PDouble/PDoubleTable
o One of the few objects that can be created using the New operator in VBA
o Internally used for representing double precision values that have units and a
mask indicating the source of the data
o PDoubleTable is a vector of values and PDouble is a single value
o Powerful units conversion utilities for VBA
o PLong/PLongTable/PString also present for long, vector of longs, and string
data. No units conversion need for these objects.
Flash
o Used to perform flash calculations in VBA
o Must create with the New operator
o Uses the FlashData object to provide and return data in flash calculations
o Provides a Solve and SolveFromGuess method. Should check return of
Solve for convergence. Return value should be >= pmxConverged for
converged solutions and >= pmxApproxSoln for approximate solutions.\
o Common flash variables include temperature, pressure, fraction vapor,
enthalpy, entropy, volume, or density.
o Two independent flash variables required
FlashData
o Used in conjunction with the Flash object
o Must create with the New operator
o All data specified and returned in SI units
o Must set the environment property and overall composition
o Passed to Solve or SolveFromGuess methods of the Flash object
o Upon converged return, contains results of flash calculations including
compositions, number of phases present and quantity of each phase present
o Allows for calculation of other non-flash properties such as viscosities,
thermal conductivities, surface tensions, etc.

16
Exercises Using VBA
Exercise 1: Listing all PStream names in a Project
This exercise illustrates accessing PStream and Flowsheet data in a project
Open the Example file MEA Dehy in the Multiple Flowsheet examples
ProMax defines an object variable named ProMaxProject which is available in
the VBE of Visio used with ProMax and OLE Embedded Excel Workbooks. It is a
reference to the current project.
Enter the following code into the ThisDocument class VBE of Visio
Sub DumpPStreams()
Dim PS As ProMax.PStream, FS As ProMax.Flowsheet

For Each FS In ProMaxProject.Flowsheets


For Each PS In FS.PStreams
Debug.Print FS.Name & ": " & PS.Name
Next
Next
End Sub

Execution of this macro will dump all PStreams in the project along with the name
of the containing flowsheet into the Immediate window.
The ProMax.PStream and ProMax.Flowsheet could be shortened to just
PStream and Flowsheet. However, the "ProMax." operator is a scope
resolution operator so that Intellisense only displays information from the ProMax
type library. Further, it is required for scenarios when more than one type library is
present that defines an object called PStream or Flowsheet.

17
Exercise 2: Listing all Component names in All
Environments in a Project
This exercise illustrates accessing component and species data for an environment
Open the Example file MEA Dehy in the Multiple Flowsheet examples
Enter the following code into the ThisDocument class VBE of Visio
Sub DumpEnvironmentComponentNames()
Dim C As ProMax.Component, E As ProMax.Environment
For Each E In ProMaxProject.Environments
For Each C In E.Components
Debug.Print E.Name & ": " & C.Species.SpeciesName.Name
Next
Next
End Sub

Create another macro called DumpEnvironmentComponentCASRN and change


the Name property call on the SpeciesName to CASRN to cause the CAS
registry number for each component can be listed
The Species object provides access to other important species data including
molecular weights, critical constants, acentric factors, vapor pressure, ideal gas heat
capacity, etc.

Exercise 3: List the Names of all Components used in a


Flowsheet Environment
This exercise illustrates accessing component and species data for the environment
assigned to a flowsheet
Open the Example file MEA Dehy in the Multiple Flowsheet examples
Enter the following code into the ThisDocument class VBE of Visio
Sub DumpFlowsheetComponentNames()
Dim C As ProMax.Component, FS As ProMax.Flowsheet

For Each FS In ProMaxProject.Flowsheets


For Each C In FS.Environment.Components
Debug.Print FS.Name & ": " & C.Species.SpeciesName.Name
Next
Next
End Sub

Note the similarity and differences with the previous exercise

18
Exercise 4: Units Conversion using the PDouble Object
Start Microsoft Excel with a blank workbook
Open the VBE and create a new module by right clicking the Modules entry in the
project tree and select Insert->Module
Enter the following code into the new module
Function UnitsConvert(Value As Double, FromUnits As String, Optional ToUnits As String)
On Error GoTo EH
Dim PMX As New ProMax.ProMax, Prj As ProMax.Project, PD As New ProMax.PDouble
Set Prj = PMX.New
PD.Value(FromUnits) = Value
If Len(ToUnits) = 0 Then
UnitsConvert = PD.SIValue
Else
UnitsConvert = PD.Value(ToUnits)
End If
Exit Function

EH:
MsgBox Err.Description
End Function

The module is used so the function can be called from a worksheet in the workbook
Add the following formula to cell D1: =UnitsConvert(A1, B1, C1)
This will allow values entered in A1 with units in B1 to be converted to units in C1.
If the C1 argument is not passed to the function (it is optional), the UnitsConvert
function will convert the value to SI units.
Function has relatively unsophisticated error handling and may give errors before
data is completely entered
To make UnitsConvert execute faster, the PMX and Prj variables can be removed
from the scope of the UnitsConvert function and either marked Public or
Private:
Private PMX As New ProMax.ProMax, Prj As ProMax.Project
Function UnitsConvert(Value As Double, FromUnits As String, Optional ToUnits As String)
On Error GoTo EH
Dim PD As New ProMax.PDouble
If Prj Is Nothing Then Set Prj = PMX.New
PD.Value(FromUnits) = Value
If Len(ToUnits) = 0 Then
UnitsConvert = PD.SIValue
Else
UnitsConvert = PD.Value(ToUnits)
End If
Exit Function

EH:
MsgBox Err.Description
End Function

19
Exercise 5: Generate Saturated Steam Properties Using
NBS Steam Tables Package
Create a blank workbook in Microsoft Excel
Open the VBE in Excel and add a reference to BR&E ProMax using Tools-
>References
Enter the following code into the ThisWorkbook class

Option Explicit

Sub NBSSteamTables()

Dim PMX As New ProMax.ProMax, Prj As ProMax.Project

Set Prj = PMX.New

' Add an environment, set the property package, and add water to the component list

Dim Env As ProMax.Environment

Set Env = Prj.Environments.Add

Env.PhysPropMethodSet.LoadPackage "NBS Steam Tables"

Env.Components.Add "Water"

' Loop from the triple point to the critical point calculating desired properties.

' All properties are in SI units.

Dim PP As ProMax.PhysProp, Status As Long, T As Double, P As Double, R As Integer

Set PP = Env.PhysProp

R = 1

For T = 273.16 To 647.126 ' T in K

' The pmxUseTemperature mask tells the function that the temperature argument should

' be used and the pressure should be computed. Using pmxUsePressure would allow for the

' saturation temperature to be computed based on pressure

P = PP.CalcPure(pmxVaporPressure, pmxLLiquidPhase, pmxUseTemperature, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 1).Value = T ' T in K

Sheet1.Cells(R, 2).Value = P ' P in Pa

' Saturated liquid properties

' H in J/gmole, S in J/(gmole*K), V in m^3/gmole, Rho in gmole/m^3, G in J/gmole, and

' Cp in J/(gmole*K)

Sheet1.Cells(R, 3).Value = PP.CalcPure(pmxMolarEnthalpy, pmxLLiquidPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 4).Value = PP.CalcPure(pmxMolarEntropy, pmxLLiquidPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 5).Value = PP.CalcPure(pmxMolarVolume, pmxLLiquidPhase, pmxNullPropMask, Status, T, P, 0)

20
If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 6).Value = 1 / Sheet1.Cells(R, 5).Value

Sheet1.Cells(R, 7).Value = PP.CalcPure(pmxMolarGibbs, pmxLLiquidPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 8).Value = PP.CalcPure_dT(pmxMolarEnthalpy, pmxLLiquidPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

' Saturated vapor properties

Sheet1.Cells(R, 9).Value = PP.CalcPure(pmxMolarEnthalpy, pmxVaporPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 10).Value = PP.CalcPure(pmxMolarEntropy, pmxVaporPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 11).Value = PP.CalcPure(pmxMolarVolume, pmxVaporPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 12).Value = 1 / Sheet1.Cells(R, 11).Value

Sheet1.Cells(R, 13).Value = PP.CalcPure(pmxMolarGibbs, pmxVaporPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

Sheet1.Cells(R, 14).Value = PP.CalcPure_dT(pmxMolarEnthalpy, pmxVaporPhase, pmxNullPropMask, Status, T, P, 0)

If Status And pmxPhysPropFailure Then GoTo Error

R = R + 1

Next

Exit Sub

Error:

MsgBox "An error occurred in PhysProp calculation: " & Status

End Sub

The PhysProp object in ProMax uses strict SI units


The above code calculates the vapor pressure, molar enthalpy, molar entropy, molar
volume, molar density, molar Gibbs, and molar heat capacity of the saturated vapor
and liquid
The results are displayed from the triple point temperature to the critical point temperature

21
Exercise 6: Tabulate in Excel the Effect of TEG
Circulation Rate on Water Content
Open the Basic Dehydration Unit Example in ProMax. It is desired to vary the flow
of glycol from 3 to 25 gpm by 2 gpm and determine the effect of circulation rate on
the residual water content of the dry gas.
Open PStream 22 and delete the flow rate calculator
Add an OLE embedded workbook to the project for tabulating the results
In the Visio VBE add reference to Microsoft Excel 11.0 Object Library
Enter the following code in the ThisDocument class of the Visio VBE:

Sub H2OResidual()
Dim V As Double, R As Integer, WS As Worksheet
Set WS = ProMaxProject.ExcelWorkbooks(0).Worksheets("Sheet1")

' Change flow from 3 gpm to 25 gpm by 2 gpm. If no units are specified on the
' PDouble.Value property, the value property returns and sets the value in the
' units that are currently selected for the property in the project.
R = 1
For V = 3 To 25 Step 2
ProMaxProject.Flowsheets(0).PStreams.Item("22").Phases(pmxTotalPhase). _
Properties.Item(pmxPhaseStdLiqVolumeFlow).Value = V
ProMaxProject.Solver.Solve True
WS.Cells(R, 1).Value = V
WS.Cells(R, 2).Value = _
ProMaxProject.Flowsheets(0).PStreams.Item("4").Analyses. _
Item("Freeze 4").Properties(pmxFH2OContent).Calculate.Value
R = R + 1
Next
End Sub

If desired, you do not have to split the long lines with a _ character as in the above
code. This was only done to fit the code in the allowed margins of this document.

22
Exercise 7: Compute the Bubble and Dew Point
Temperatures of a Binary System
Create a blank ProMax project
Initialize the Environment to use NRTL-PR package with Ethanol and Water as the
two components in the system
It is required to compute the bubble point temperature and dew point at 1 atm
pressure for a 50:50 mixture this system
Enter the following code in the ThisDocument class of the Visio VBE:
Function UnitsConvert(Value As Double, FromUnits As String, ToUnits As String)
Dim PD As New PDouble
PD.Value(FromUnits) = Value
UnitsConvert = PD.Value(ToUnits)
End Function
Sub DPBP()
Dim F As New ProMax.Flash, FD As New ProMax.FlashData, Status As Long, Z() As Double
ReDim Z(0 To 1)

' Initialize FlashData with environment and composition


FD.Environment = ProMaxProject.Flowsheets(0).Environment
Z(0) = 0.5
Z(1) = 1# - Z(0)
FD.Composition(pmxTotalPhase) = Z
Status = F.Solve(pmxFlashPressure, UnitsConvert(1, "atm", "Pa"), pmxFlashFracVapor, 0#, FD)
If Status >= pmxApproxSoln Then Debug.Print UnitsConvert(FD.Property(pmxPhaseTemperature), "K", "C")
Status = F.Solve(pmxFlashPressure, UnitsConvert(1, "atm", "Pa"), pmxFlashFracVapor, 1, FD)
If Status >= pmxApproxSoln Then Debug.Print UnitsConvert(FD.Property(pmxPhaseTemperature), "K", "C")
End Sub

The Flash and FlashData objects in ProMax require strictly SI units


The Flash.Solve method requires two flash variables to be specified. In this
case, the pressure and vapor fraction have been specified.
A UnitsConvert function similar to that presented earlier is present to assist in
converting to and from SI units. The SI units for pressure and temperature are Pa
and K, respectively.
This system is a well known azeotropic system. To determine the azeotropic
composition, change the above code to generate a Txy diagram for the binary
system at 1 atm by tabulating and plotting the results in Microsoft Excel. Only the
bubble point calculation needs to be made and the composition of the vapor can be
obtained from the FlashData object Composition (FD.Composition)
property. The composition will need to be varied from pure ethanol to pure water.
Use a step size of 0.01 mole fraction to generate enough points for a good quality
plot.

23
This problem can also be solved using VBA in Excel without starting the ProMax
GUI. Create a blank Excel workbook and generate the Txy diagram for this system
in Excel. The environment will need to be initialized with the NRTL-PR package
as well as the ethanol and water components. The code from the previous exercise
can be copied and pasted as a starting point.
CO2 and ethane also form an azeotropic system that can cause fractionation
problems in gas processing facilities. To determine the azeotropic composition,
change the code to generate a Txy diagram for this system using the Peng-Robinson
equation of state package. What is the azeotropic composition at 300 psia?

24
Appendices

A. BR&E ProMax Partial Object Model with Commonly Used Properties and Methods
B. PStream Structure and Properties Enums
C. Analysis Structure and Properties Enums
D. Block Structure and Properties Enums I (Basic Blocks)
E. Block Structure and Properties Enums II (Columns, Pipelines, Recycles)
F. Block Structure and Properties Enums III (HEX Rating)
G. Environment and Reactive
H. Additional Project Objects
I. Enumerators by Use I (Blocks, Units)
J. Enumerators by Use II (Column Hardware, Specification and Constraints, Separator
Sizing, Single Oils, Compact Rating)
K. Enumerators by Use III (Reactors and Reactions, Calculators, Plate Frame Rating)

25
ProMax
+Project
-ExcelApp
-ID Project
-Name -Calculators Environment
-Version +EnergyBudgets -Components
-VisioApp Environments
+Environments -FlashOptions
+GetShortMoniker() +ExcelWorkbooks +Count -GEModelEvalTemperature : PDouble
+GetShortMonikers() +Flowsheets +Item : Environment -FreezeFormationDeltaT : PDouble
+Next() +Name +Project -ModelParameters
+New() +Oils +Add() : Environment +Name
+Open() +Path -Notes
+VisioAsGUI() : Boolean -Reactions +Project
-ReactionSets ExcelWorkbooks +PhysProp
+Recoveries +PhysPropMethodSet
-Solver +Count
-PoyntingIntervals : PLong
+SpeciesCache +Item
UnitSet -ReactionSets
+SpeciesNames +Add() -RxnKeqSet
-FractionAsPercentage : Boolean
-UnitSet
-Name +Copy()
-UserValueSets Solver
-PressureInGauge : Boolean +CreatePhysProp()
+VisioDocument
-Project -Parent +Delete()
+...
+GetExternalUnits(pmxUnitsEnum)() : String -Project +Edit()
+ClearAllCalculated()
+GetInternalUnits(pmxUnitsEnum)() : String +Solve()
+Close()
+GetNames(String())()
+Save()
+SaveAs()

Components
Oils PhysProp
+Count
+Count +Environmnent +Components()
+Item : BaseOil SpeciesCache +InstalledOils : Oils +Environment
+Project +Item : Species +Item : Component +CalcBinary() : Double
+AddOil() : Oil +ItemFromCASRN : Species +Project +CalcBinary_dT() : Double
+AddSingleOil() : SingleOil +ItemFromFormula : Species +Add() : Component +CalcComponent()
+Project +Remove() +CalcComponent_dT()
+Reorder() +CalcInterphase() : Double
SingleOil +SetItems() +CalcInterphase_dT() : Double
-EditCopy : SingleOil +CalcMixture() : Double
+Name +CalcMixture_dT() : Double
SpeciesNames Component +CalcPure() : Double
-Notes
-OilPropMethodSet -Count -ActivePhase : pmxPhaseEnum +CalcPure_dT() : Double
-Original : SingleOil +Item : SpeciesName +Environment +ReloadAllProperties()
-Project +ItemFromCASRN : SpeciesName +Henry : Boolean
-Properties : pmxOilPropEnum +ItemFromFormula : SpeciesName +PhaseInitiator : Boolean
-ViscosityType +Project +Species
+Delete()
+Edit()
+Open() : SingleOil
+Update() Species
+ConstProp(pmxPureSpeciesConstPropEnum) : PDouble PropertySolver
Oil +ConstPropSI(pmxPureSpeciesConstPropEnum) : PDouble -CalculatedVariable
+Project -Project
-Basis : pmxCompositionEnum
+SpeciesName -Properties : Base Property
-BlendData : PDoubleTable
-VarProp(pmxPureSpeciesVarPropEnum) -Status : Long
-BPCurve
-Cuts +Delete()
-EditCopy : Oil +EnthalpyFormation() : PDouble
-HighTViscCurve +GibbsFormation() : PDouble
-LowTViscCurve «enumeration»
-LightEnds pmxPropertySolverPropEnum
-MWCurve SpeciesName
+CASRN : Long +pmxPropertySolverError
-Notes
+Charge : Long +pmxPropertySolverValue
+Name
-ElementalMakeup : String +pmxPropertySolverLowerBound
-OilPropMethodSet
+Formula : String +pmxPropertySolverUpperBound
-Original : Oil
+Name : String +pmxPropertySolverBoundStep
-Project
+PrimaryName : String +pmxPropertySolverMinimizer
-SGCurve
-Project +pmxPropertySolverInternalAlgorithm
-ViscosityType
-... +pmxPropertySolverIterations
+Delete() +pmxPropertySolverMaxIterations
+Edit() +pmxPropertySolverWeighting
+GetCutLimits() +pmxPropertySolverPriority
+Open() : Oil +pmxPropertySolverActive
26
+SetCutLimits() +pmxPropertySolverGroup
+Solve()
+Update()
Flowsheet
+Blocks

Calculators
BR&E ProMax Partial Object Flowsheets
+Count
+Environment
+Name
+Count Model with Commonly Used +Item : Flowsheet
+Project
-Notes
+Project
+Item : Calculator
-Project Properties and Methods +Add() : Flowsheet
-Import() : Flowsheet
+PStreams
+QStreams
+Add() : Calculator
-Solver
+VisioPage
Calculator +CreatePStream()
+CreateQStream()
-CalcVariables +Delete()
-Name
«enumeration»
-Notes
pmxCodeSourceEnum
-Project
-Results : Double +pmxCodeSourceVBA
+pmxCodeSourceScript Blocks QStreams PStreams
+Calculate()
+pmxCodeSourceExcel +Count +Count +Count
+Delete()
+pmxCodeSourceExternal +Flowsheet +Flowsheet +Flowsheet
+GetCalculatorSource()
+pmxCodeSourceSimple +Item : Block +Item : QStream +Item : PStream
+GetCalculatorString() : String
+pmxCodeSourceQRecycle +Project +Project +Project
+GetCalculatorType() : pmxCalculatorTypeEnum
+GetCodeSource() : pmxCodeSourceEnum +Add() : Block +Add() : QStream +Add() : PStream
+GetTemporaryArgument()

Block PStream
«enumeration» QStream
+ConnectionsCount +Analyses
pmxCalculatorTypeEnum +EnergyConnections : QConnections +Energy : PDouble +Flowsheet
CalcVariables +Flowsheet
+pmxCalculatorSolver +Flowsheet +FromConnection : Block
-Count +pmxCalculatorSpecifier +Inlets : PConnections +FromConnection : Block -InstalledOil : Oil
-Item : CalcVariable +Name +Name +Name
-Project -Notes -Notes -Notes
-Calculator +Outlets : PConnections +Parent +Parent : Flowsheet
+Add() : CalcVariable +Parent +Project +Phases
+Project +Status : Long +Project
+Properties : Base Property +TimeModified +Status : Long
+Status : Long +TimeSolved -TimeModified
Block Properties Enum +ToConnection : Block
-TimeModified -TimeSolved
-TimeSolved +VShape -ToConnection : Block
+Type : pmxBlockTypesEnum +Clear() +VShape
CalcVariable +VShape +Delete() +Clear()
+Clear() +Solve() +CopyFrom()
-Calculator
-MeasuredVariables +Delete() +Delete()
-Moniker : String +Solve() +Flash()
-Name +GetFlashSpec()
-Project +InstallOil()
-Property Base Property
-PropertySolver -Label
-Units : String -Mask
+Delete() -Name
-Parent
-Project
-Type
+Clear() PString
PDouble PDoubleTable PLong PLongTable
+Label +Label : string(idl) +Label +Units +Label
MeasuredVariables
+Mask +Mask : long(idl) +Mask +UnitsEnum +Mask
-Count +Maximum +Maximum : double(idl) +Maximum +RowCount +Maximum
-Item : MeasuredVariable +Minimum +Minimum : double(idl) +Minimum +UnitsIndex +Minimum
-Project +Name +Name : string(idl) +Name +SIValues +Name
-Calculator +Parent +Parent : object(idl) +Parent +SIValues1 +Parent
+Add() : MeasuredVariable +Project +Project : Project +Project +Types +Project
+SIValue +RowCount : long(idl) +Types +Values1 +Types
+SIValue1 +SIValues +Value1 +Values2 +Value1
+Type +SIValues1 +Value2 +ValuesAsStrings +Value2
Base Property Enums
+Units +Type +ValueAsString +Label +Calculate()
MeasuredVariable -pmxPDouble +UnitsEnum +Units : string(idl) +Mask +Clear()
-pmxPLong +Calculate()
-CalcVariable -UnitsIndex +UnitsEnum +Clear() +Maximum
-pmxPString +Value1 +UnitsIndex : long(idl) +Minimum
-Moniker : String
-pmxPDoubleTable +Value2 +Values1 +Name
-Name
-pmxPLongTable +ValueAsString +Values2 +Parent
-Property
-Units : String +Calculate() +ValuesAsStrings +Project
+Delete() +Clear() +Calculate() : PDoubleTable +Calculate() 27
+Project() +Clear() +Clear()
Flowsheet
+Blocks
PStream Structure and Properties Enums
+Environment
+Name
-Notes
+Project
+PStreams
+QStreams
PStreams
-Solver
+VisioPage +Count
+CreatePStream() +Flowsheet
+CreateQStream() +Item : PStream
+Delete() +Project
+Add() : PStream
Stage
Blocks -<Block Inheritance>
-Column : StagedColumn
+Count
-HardwareProperties*(pmxStageHardwareTypesEnum) : Properties
+Flowsheet
-Internal : PStream
+Item : Block
+Project
+Add() : Block
«enumeration»
Internal PStream
pmxBlockTypesEnum
+pmxCompExpBlock +Analyses
+pmxCRHEXBlock +Flowsheet
+pmxDividerBlock +FromConnection : Block
Block +Name
+pmxJTValveBlock
+ConnectionsCount +pmxMakeupBlock -Notes
+EnergyConnections : QConnections +pmxMixerSplitterBlock +Parent : Block
+Flowsheet +pmxMSHEXBlock +Phases
+Inlets : PConnections +pmxPipelineBlock +Project
+Name +pmxPipeSegmentBlock +Status : Long
-Notes +pmxPumpBlock -TimeModified
+Outlets : PConnections +pmxRecycleBlock -TimeSolved
+Parent +pmxSaturatorBlock -ToConnection : Block
SSHEX
+Project +pmxSeparatorBlock +VShape
+Properties : Base Property +pmxSSHEXBlock -<Block Inheritance> -InstalledOil : Oil
+Status : Long +pmxStageBlock -Internals() : PStream +Clear()
-TimeModified +pmxStagedColumnBlock -MSHEX +CopyFrom()
-TimeSolved +pmxXFSConnectorBlock -QManager +Delete()
+Type : pmxBlockTypesEnum +pmxQRecycleBlock +CalculateInternals() +Flash()
+VShape +pmxReactorBlock +GetFlashSpec()
+Clear() +pmxCRReactorBlock +InstallOil()
+Delete() +pmxVLReactorBlock
+Solve() PConnection
+pmxNEQReactorBlock
-Block PStreamList
-ID
-Count
-Name
-Item : PStream
PConnections -PStreamList : PStreamList
-Project
-Project
-Block
-PConnections
-Count
-Index +Delete()
-Item : PConnection
QStream
-ItemByID : PConnection
-Project +Energy : PDouble
+Flowsheet
+FromConnection : Block
QConnection +Name
-Block QStreamList -Notes
QConnections -ID +Parent
-Count
-Block -Name +Project
-Item : QStream
-Count -Project +Status : Long
-Project
-Index -QConnections +TimeModified
-Item : QConnection -QStreamList +TimeSolved
-ItemByID : QConnection +Delete() +ToConnection : Block
-Project +VShape
+Clear()
+Delete()
+Solve()

28
Analyses
Analysis Types Enums
+Count
-pmxAmineAnalysis
+Item : Analysis
-pmxCombustionAnalysis
+Parent
-pmxDistillationCurveAnalysis
+Project
-pmxFreezeAnalysis
+Add(pmxAnalysisTypesEnum)() : Analysis -pmxFuelAnalysis
-pmxLineSizingAnalysis
-pmxPhaseEnvelopeAnalysis
-pmxReliefValveSizingAnalysis
Analysis -pmxVaporPressureAnalysis
+Name
+Parent : PStream
+Phase
«enumeration»pmxPhasePropEnum
+Project
+Properties +_pmxPhasePropUnknown
+PropertiesExt +pmxPhaseTemperature
+PropertiesToCalculate +pmxPhasePressure
+Status +pmxPhaseMoleFracVapor
PStream
+Type +pmxPhaseMoleFracLLiquid
+Analyses +pmxPhaseMoleFracHLiquid
+Delete()
+Flowsheet +pmxPhaseMassFracVapor
+GetConditoins()
+FromConnection : Block +pmxPhaseMassFracLLiquid
+SetConditions()
-InstalledOil : Oil +pmxPhaseMassFracHLiquid
+Solve()
+Name +pmxPhaseVolFracVapor
-Notes +pmxPhaseVolFracLLiquid
+Parent : Flowsheet +pmxPhaseVolFracHLiquid
+Phases +pmxPhaseMoleWeight
+Project +pmxPhaseMolarDensity
+Status : Long +pmxPhaseMassDensity
-TimeModified «enumeration» +pmxPhaseMolarVolume
-TimeSolved Phases pmxPhaseEnum +pmxPhaseMassVolume
-ToConnection : Block +pmxVaporPhase +pmxPhaseMolarFlow
+Count
+VShape +pmxLLiquidPhase +pmxPhaseMassFlow
+Item(pmxPhaseEnum)
+Clear() +Project +pmxHLiquidPhase +pmxPhaseVapVolumeFlow
+CopyFrom() +PStream +pmxMixedLiquidPhase +pmxPhaseLiqVolumeFlow
+Delete() +pmxTotalPhase +pmxPhaseStdVapVolumeFlow
+Flash() +pmxPhaseNormalVapVolumeFlow
+GetFlashSpec() +pmxPhaseStdLiqVolumeFlow
+InstallOil() +pmxPhaseCompressibility
+pmxPhaseSpecificGravity
+pmxPhaseAPIGravity
+pmxPhaseEnthalpy
«enumeration» +pmxPhaseMolarEnthalpy
pmxCompositionEnum +pmxPhaseMassEnthalpy
Phase +pmxMolarFlowBasis +pmxPhaseEntropy
+Composition(pmxCompositionEnum) : PDoubleTable +pmxMassFlowBasis +pmxPhaseMolarEntropy
+Flowsheet +pmxVolFlowBasis +pmxPhaseMassEntropy
+Project +pmxStdVapVolFlowBasis +pmxPhaseGibbs
+Properties +pmxNormalVapVolFlowBasis +pmxPhaseMolarGibbs
+PStream +pmxStdLiqVolFlowBasis +pmxPhaseMassGibbs
+Status : Long +pmxMolarFracBasis +pmxPhaseInternalEnergy
+Type +pmxMassFracBasis +pmxPhaseMolarInternalEnergy
+pmxVolFracBasis +pmxPhaseMassInternalEnergy
+pmxStdLiqVolFracBasis +pmxPhaseMolarCp
+pmxPhaseMassCp
+pmxPhaseMolarCv
+pmxPhaseMassCv
+pmxPhaseIGCpCvRatio
Properties +pmxPhaseCpCvRatio
+pmxPhaseDynViscosity
+Count +pmxPhaseKinViscosity
+Item : Base Property +pmxPhaseThermalCond
+Parent +pmxPhaseSurfaceTension
+Project +pmxPhasePseudoCriticalTemperature
+pmxPhasePseudoCriticalPressure
+pmxPhaseNetIGHeatValue
+pmxPhaseNetLiquidHeatValue
+pmxPhaseGrossIGHeatValue
+pmxPhaseGrossLiquidHeatValue

29
PStream
+Analyses
+Flowsheet
+FromConnection : Block
-InstalledOil : Oil
+Name
-Notes Analyses
+Parent : Flowsheet
+Phases +Count
+Project +Item : Analysis
+Status : Long +Parent
-TimeModified +Project
-TimeSolved +Add(pmxAnalysisTypesEnum)() : Analysis
-ToConnection : Block
+VShape
+Clear()
Analysis
+CopyFrom() Analysis Types Enums
+Delete() +Name
+Flash() +Parent : PStream -pmxAmineAnalysis
+GetFlashSpec() +Phase -pmxCombustionAnalysis
+InstallOil() +Project -pmxDistillationCurveAnalysis
+Properties -pmxFreezeAnalysis
+PropertiesExt -pmxFuelAnalysis
+PropertiesToCalculate -pmxLineSizingAnalysis
+Status -pmxPhaseEnvelopeAnalysis
+Type -pmxReliefValveSizingAnalysis
+Delete() -pmxVaporPressureAnalysis
+GetConditoins()
+SetConditions()
+Solve()

Amine Analysis Enums Distillation Curves Analysis Enums Freeze Analysis Enum
-pmxAACO2LoadingMassPerVol -pmxDistillationCurveDryBasis -pmxFSolidsFormationT
-pmxAACO2LoadingVolPerVol -pmxDistillationCurveNumberOfSteps -pmxFDegreesAboveSolidsFormationT
-pmxAACO2LoadingMolePerMoleAmine -pmxDistillationCurvePressure -pmxFH2OContent
-pmxAAH2SLoadingMassPerVol -pmxDistillationCurveMinNBPThreshold -pmxFH2ODewPtT
-pmxAAH2SLoadingVolPerVol -pmxDistillationCurveVolFrac -pmxFHydrateThi
-pmxAAH2SLoadingMolePerMoleAmine -pmxDistillationCurveMoleFrac -pmxFHydrateThiStruct
-pmxAATotalAcidGasLoading -pmxDistillationCurveMassFrac -pmxFHydrateP
-pmxAApH -pmxDistillationCurveTBP -pmxFHydratePStruct
-pmxAAMolarity -pmxDistillationCurveD86 -pmxFH2OFreezeThi
-pmxAAIncludeAmmonia -pmxDistillationCurveD1160 -pmxFCO2FreezeThi
-pmxDistillationCurveD2887 -pmxFHydrateThiRegion
-pmxDistillationCurveEFV -pmxFHydratePRegion
-pmxFH2OFreezeThiRegion
-pmxFCO2FreezeThiRegion
Combustion Analysis Enum -pmxFHydrateTmid
-pmxCACombustionO2Requirement -pmxFHydrateTmidStruct
-pmxCAGrossHeatOfCombustionIG -pmxFHydrateTmidRegion
-pmxCAGrossHeatOfCombustionLiq -pmxFH2OFreezeTmid
-pmxCANetHeatOfCombustionIG -pmxFH2OFreezeTmidRegion
-pmxCANetHeatOfCombustionLiq -pmxFCO2FreezeTmid
-pmxCAWobbeIndex -pmxFCO2FreezeTmidRegion
-pmxFHydrateTlo
-pmxFHydrateTloStruct
-pmxFHydrateTloRegion
-pmxFH2OFreezeTlo
-pmxFH2OFreezeTloRegion
-pmxFCO2FreezeTlo
-pmxFCO2FreezeTloRegion

30
Analysis Structure and Properties Enums

Block
SSHEX +ConnectionsCount
+EnergyConnections : QConnections
-<Block Inheritance>
+Flowsheet
-Internals() : PStream
+Inlets : PConnections
-MSHEX
+Name
-QManager
-Notes
+CalculateInternals() +Outlets : PConnections
Internal PStream +Parent
+Analyses +Project
+Flowsheet +Properties : Base Property
+FromConnection : Block Stage +Status : Long
+Name -TimeModified
-<Block Inheritance>
-Notes -TimeSolved
-Column : StagedColumn
+Parent : Block +Type : pmxBlockTypesEnum
-HardwareProperties*(pmxStageHardwareTypesEnum) : Properties
+Phases +VShape
-Internal : PStream
+Project +Clear()
+Status : Long +Delete()
-TimeModified +Solve()
-TimeSolved
-ToConnection : Block
+VShape
-InstalledOil : Oil
+Clear()
+CopyFrom()
+Delete()
+Flash()
+GetFlashSpec()
+InstallOil()

Fuel Properties Analysis Enums Phase Envelope Analysis Enums Relief Valve Sizing Enums Vapor Pressure Analysis Enums
-pmxFPDryBasis -pmxPEMoleFracVapor -pmxRVSAStandards -pmxVPDryBasis
-pmxFPCetaneIndex -pmxPETemperature -pmxRVSAValveType -pmxVPBubblePointT
-pmxFPCetaneIndexCorr -pmxPEPressure -pmxPVSAEffectiveDischargeArea -pmxVPBubblePointP
-pmxFPAnilinePoint -pmxPEMolarEnthalpy -pmxRVSAReliefTemperature -pmxVPDewPointT
-pmxFPAnilinePointCorr -pmxPEMolarEntropy -pmxRVSAReliefPressure -pmxVPDewPointP
-pmxFPFlashPoint -pmxPEMolarDensity -pmxRVSASetPressure -pmxVPTrueVaporPressure
-pmxFPAbsVisc100F -pmxPEMinimumPressure -pmxRVSAOverPressure -pmxVPReidVaporPressure
-pmxFPAbsVisc210F -pmxPEMinimumTemperature -pmxRVSAOverPressureFraction
-pmxFPParaffinicFraction -pmxPEMinMoleFracVapor -pmxRVSABackPressure
-pmxFPNaphthenicFraction -pmxPEMaxMoleFracVapor -pmxRVSARequiredMassFlow
-pmxFP ... -pmxPE ... -pmxRVSA ...

Line Sizing Analysis Enums


-pmxLSHorizLinearPDrop
-pmxLSNomSize
-pmxLSAbsoluteRoughness
-pmxLSAngle
-pmxLSMaxVelocity
-pmxLSSchedule
-pmxLSCorrosionAllowance
-pmxLSJointWeldEff
-pmxLSPressureCode
-pmxLSANSIB31_8DesignFactor
-pmxLS ...

31
Flowsheet
+Blocks Blocks
+Environment Block
+Name +Count
+Flowsheet +ConnectionsCount
-Notes
+Item : Block +EnergyConnections : QConnections Divider JTValve
+Project
+Project +Flowsheet
+PStreams -<Block Inheritance> -<Block Inheritance>
+Add() : Block +Inlets : PConnections
+QStreams
+Name
-Solver
-Notes
+VisioPage
+Outlets : PConnections
+CreatePStream() +Parent «enumeration» «enumeration»
+CreateQStream() +Project pmxDividerEnum pmxJTValvePropEnum
+Delete() +Properties : Base Property +pmxDividerFractionExtracted +pmxJTValvePDrop
+Status : Long +pmxDividerBulkDeltaP +pmxJTValveJTCoefficient
PStreams -TimeModified +pmxDividerBulkDeltaT
-TimeSolved +pmxDividerExtractDeltaP
+Count
+Type : pmxBlockTypesEnum +pmxDividerExtractDeltaT
+Flowsheet
+VShape
+Item : PStream
+Project +Clear()
+Delete()
+Add() : PStream
+Solve()

SSHEX
PStream MSHEX
-<Block Inheritance>
+Analyses -Count
-Internals() : PStream
+Flowsheet -Item : SSHEX
CRReactor -MSHEX
+FromConnection : Block -QManager
-QManager
-InstalledOil : Oil -<Block Inheritance> +AddSSHEX() : SSHEX
+Name -Reactor +CalculateInternals()
-Notes -SSHex
+Parent : Flowsheet
+Phases
+Project
+Status : Long CRHEX
-TimeModified «enumeration» Reactor «enumeration»
-<MSHEX Inheritance>
-TimeSolved pmxBlockTypesEnum -<Block Inheritance> pmxSSHEXPropEnum
-ToConnection : Block -Constraints +pmxSSHEXPDrop
+pmxCompExpBlock
+VShape -ReactionSet +pmxSSHEXDeltaT
+pmxCRHEXBlock
+Clear() +pmxDividerBlock +pmxSSHEXDuty
+CopyFrom() +pmxJTValveBlock +pmxSSHEXCurveType
+Delete() +pmxMakeupBlock +pmxSSHEXCurveIncrements
+Flash() +pmxMixerSplitterBlock VLReactor
+GetFlashSpec() +pmxMSHEXBlock
+InstallOil() +pmxPipelineBlock -<Reactor Inheritance>
+pmxPipeSegmentBlock
+pmxPumpBlock
+pmxRecycleBlock «enumeration»
+pmxSaturatorBlock pmxReactorPropEnum
+pmxSeparatorBlock
+pmxReactorDeltaP
+pmxSSHEXBlock
+pmxReactorDuty
+pmxStageBlock
+pmxReactorConversion
+pmxStagedColumnBlock
+pmxReactorPFRSolutionMethod
+pmxXFSConnectorBlock
+pmxReactorMaxPhases
+pmxQRecycleBlock
+pmxReactorYield
+pmxReactorBlock
+pmxReactorIVMethod
+pmxCRReactorBlock
+pmxReactorBypassFraction
+pmxVLReactorBlock
+pmxReactorMaxAvailableConstraints
+pmxNEQReactorBlock
+pmxReactorIncrements
+pmxReactorGibbsSet
+pmxReactorType
+pmxReactorIncrementType
+pmxReactorReactionExtent
+pmxReactorReactionConversion
+pmxReactorYieldComponent
+pmxReactorGibbsReactive
Block Structure and +pmxReactorMaxTemperature
+pmxReactorDeltaT
Properties Enums I +pmxReactorFracVapor
+pmxReactorFracLLiquid
(Basic Blocks) +pmxReactorFracHLiquid
+pmxReactorSegments
+pmxReactorDeltaPMethod
+pmxReactorParticleDiameter
32 +pmxReactorNEQMassTransfer
«enumeration»
XFSConnector pmxXFSConnectorEnum
-<Block Inheritance> +pmxXFSThreshold
-Couple : XFSConnector +pmxXFSTransferProperty1
Makeup MixerSpllitter Saturator +pmxXFSTransferProperty2
-CoupledBlock : Block
-<Block Inheritance> -<Block Inheritance> -<Block Inheritance> -CoupledPStream : PStream +pmxXFSInletTemperature
-CoupledQStream : QStream +pmxXFSInletPressure
+pmxXFSInletVaporFraction
+pmxXFSInletMassEnthalpy
+pmxXFSOutletTemperature
«enumeration» «enumeration» «enumeration»
+pmxXFSOutletPressure
pmxMakeupPropEnum pmxSplitterPropEnum pmxSaturatorPropEnum
+pmxXFSOutletVaporFraction
+pmxMakeupPDrop +pmxSplitterPDrop +pmxSaturatorFraction +pmxXFSOutletMassEnthalpy
+pmxMakeupBulkBasis +pmxSaturatorTemperature +pmxXFSDeltaTemperature
+pmxMakeupDesiredOutletBasis +pmxSaturatorPressure +pmxXFSDeltaPressure
+pmxMakeupBulk +pmxSaturatorDeltaP +pmxXFSDeltaVaporFraction
+pmxMakeupDesiredOutlet +pmxSaturatorDeltaT +pmxXFSDeltaMassEnthalpy
+pmxSaturatorDeltaSatP +pmxXFSTemperatureTol
+pmxXFSPressureTol
+pmxXFSVaporFractionTol
+pmxXFSMassEnthalpyTol

CompExp Pump
-<Block Inheritance> +PerformanceCurves
Separator
+PerformanceCurves -<Block Inheritance>
-<SSHEX Inheritance>
-SizingProperties*
+DeleteSizingProperties()
«enumeration» «enumeration»
«enumeration» PerformanceCurves
pmxCompExpPropEnum pmxPumpPropEnum
pmxSeparatorPropEnum -Block
+pmxCompExpAdiabaticEff +pmxPumpDeltaP
+pmxSeparatorPDrop +pmxCompExpAdiabaticHead -Count +pmxPumpEfficiency
+pmxSeparatorFracVapor +pmxCompExpPolytropicEff -Item : PerformanceCurve +pmxPumpHead
+pmxSeparatorDuty +pmxCompExpPolytropicHead -Project +pmxPumpPower
+pmxSeparatorCurveType QRecycle +pmxCompExpDeltaP -Type : PLong
+pmxSeparatorCurveIncrements +pmxCompExpPRatio +Add() : PerformanceCurve
-<Block Inheritance>
+pmxSeparatorSingleLiquidPhase +pmxCompExpSpeed
-Calculator
+pmxSeparatorFracLLiquid +pmxCompExpPower
+pmxSeparatorFracHLiquid PerformanceCurve
+pmxCompExpIsentropicK
+pmxCompExpPolytropicN -Active : Boolean
-Block
-Curve
«enumeration» -Name
pmxQRecyclePropEnum -Project
-Speed : PDouble
+pmxQRecycleError
-Valid : Boolean
+pmxQRecycleCalculatedValue
+Delete()

Calculator
-CalcVariables CalcVariable PTables
-Name -Count
-Calculator
-Notes -Item : PDoubleTable
-MeasuredVariables
-Project -Label
-Moniker : String
-Results : Double -Name
-Name Curve
+Calculate() -Project -Parent
+Delete() -AllowExtrapolation : Boolean
-Property -Project
+GetCalculatorSource() -Data : PTables
-PropertySolver -RowCount : Long
+GetCalculatorString() : String -Method : pmxCurveInterpEnum
-Units : String +Add() : PDoubleTable
+GetCalculatorType() : pmxCalculatorTypeEnum -Project : Amine Analysis Enums
+Delete() -XColumn : Long
+GetCodeSource() : pmxCodeSourceEnum
+GetTemporaryArgument() +AverageX() : PDouble «enumeration»
MeasuredVariable +AverageY() : PDouble pmxCurveInterpEnum
-CalcVariable +CalcX() : PDouble
+pmxMonotonicSpline
-Moniker : String +CalcY() : PDouble
+pmxQuarticSpline
-Name +IsDataAvailable() : Boolean
+pmxLagrangeSpline
-Property +pmxLinearSpline
-Units : String
+Delete()
+Project() 33
Flowsheet Stage
+Blocks -<Block Inheritance>
Blocks -Column : StagedColumn
+Environment
+Name +Count Block -HardwareProperties*(pmxStageHardwareTypesEnum) : Properties
-Notes +Flowsheet +ConnectionsCount -Internal : PStream
+Project +Item : Block +EnergyConnections : QConnections
+PStreams +Project +Flowsheet
+QStreams +Add() : Block +Inlets : PConnections «enumeration»
-Solver +Name pmxStagedColumnPropEnum
+VisioPage -Notes
+Outlets : PConnections +pmxStagedColumnIdealStages
+CreatePStream() +pmxStagedColumnNumberTopDown
+CreateQStream() +Parent
+Project +pmxStagedColumnFlashType
+Delete() +pmxStagedColumnEfficiencyPhase
+Properties : Base Property
+Status : Long +pmxStagedColumnIterations
-TimeModified +pmxStagedColumnUseLastSolution
-TimeSolved +pmxStagedColumnAddOns
PStreams
+Type : pmxBlockTypesEnum +pmxStagedColumnDegreesOfFreedom
+Count +pmxStagedColumnBostonSullivanKb
+VShape
+Flowsheet +pmxStagedColumnMainLiquidPhase
+Item : PStream +Clear() +pmxStagedColumnPressureDrop
+Project +Delete() +pmxStagedColumnType
+Solve() +pmxStagedColumnKDamping
+Add() : PStream
+pmxStagedColumnCondenser3Phases
«enumeration» +pmxStagedColumnReboiler3Phases
pmxBlockTypesEnum +pmxStagedColumnEnthalpyModel
+pmxCompExpBlock +pmxStagedColumnMaxInitIters
PStream +pmxStagedColumnThermalEff
+pmxCRHEXBlock
+Analyses +pmxStagedColumnCalculateHydraulics
+pmxDividerBlock
+Flowsheet +pmxStagedColumnInnerLoopModel
+pmxJTValveBlock
+FromConnection : Block +pmxStagedColumnPhaseThreshold
+pmxMakeupBlock
-InstalledOil : Oil StagedColumn
+pmxMixerSplitterBlock
+Name
+pmxMSHEXBlock -<Block Inheritance>
-Notes
+pmxPipelineBlock -Condenser : Separator StagedColumnSpecifications
+Parent : Flowsheet
+pmxPipeSegmentBlock -MultiRootSolverSpec
+Phases -Count
+pmxPumpBlock -Reboiler : Separator
+Project -Column : StagedColumn
+pmxRecycleBlock -Specifications
+Status : Long -Item : StagedColumnSpecification
+pmxSaturatorBlock -Stage : Stage
-TimeModified -Project
+pmxSeparatorBlock +AttachToColumn()
-TimeSolved +Add() : StagedColumnSpecification
+pmxSSHEXBlock +DeleteLastSolution()
-ToConnection : Block
+pmxStageBlock +InsertBelow()
+VShape
+pmxStagedColumnBlock +MainColumn() : StagedColumn
+Clear() +pmxXFSConnectorBlock StagedColumnSpecification
+CopyFrom() +pmxQRecycleBlock -Column : StagedColumn
+Delete() +pmxReactorBlock -Components() : Component
+Flash() Separator
+pmxCRReactorBlock -Name
+GetFlashSpec() +pmxVLReactorBlock -<SSHEX Inheritance> -Phase : pmxPhaseEnum
+InstallOil() +pmxNEQReactorBlock -SizingProperties* -Project
+DeleteSizingProperties() -Properties*
-Source
MultiRootSolverSpec -Status
Recycle -Type : pmxStagedColumnSpecificationEnum
-Project
-<Block Inheritance> +Delete()
-Properties : Properties
-FunctionComponents() : Component
-Type : pmxMultiRootSolverEnum
-FunctionIndices() : Long «enumeration»
-MultiRootSolverSpec pmxMultiRootSolverSpecPropEnum
-Variables() «enumeration» +pmxMultiRootSolverTerminateIfSlow
+GetFlashVariables() pmxMultiRootSolverEnum +pmxMultiRootSolverUseForwardDiffs
+SetFlashVariables() +pmxAccelGauss +pmxMultiRootSolverMaxIterations
+SetInitialGuess() +pmxBFGS +pmxMultiRootSolverFactor
+pmxBrentM +pmxMultiRootSolverBoundStep
+pmxBrown +pmxMultiRootSolverFrequency
+pmxGauss +pmxMultiRootSolverMaximumParameter
+pmxHybrd +pmxMultiRootSolverMinimumParameter
+pmxLmdif +pmxMultiRootSolverWait
+pmxNewtonRaphson +pmxMultiRootSolverWaitTolerance
«enumeration» «enumeration» +pmxMultiRootSolverMaximumIncreasing
+pmxQNSS1
pmxRecyclePropEnum pmxRecycleVariablesEnum +pmxMultiRootSolverMaximumOscillations
+pmxQNSS2
+pmxRecycleError +pmxRecyclePressure +pmxQNSS3 +pmxMultiRootSolverOrder
+pmxRecycleIterations +pmxRecycleEnthalpy +pmxSimplex +pmxMultiRootSolverLineSearchMethod
+pmxRecyclePriority +pmxRecycleVaporFrac +pmxSteepestDescent +pmxMultiRootSolverUpdateHessian
+pmxRecycleFunction +pmxRecycleTemperature +pmxMultiWegstein +pmxMultiRootSolverContractionCoeff
+pmxRecycleCalculate +pmxRecycleTotalMassFlow +pmxMultiGDEM +pmxMultiRootSolverExpansionCoeff
34
+pmxRecycleWeights +pmxRecycleSpeciesFlow +pmxMultiRootSolverDefault +pmxMultiRootSolverReflectionCoeff
+pmxSparseNewtonRaphson +pmxMultiRootSolverTruncatedNewtonBounding
«enumeration»
pmxStagePropEnum SSHEX Pipeline
+pmxStageMurphreeEfficiencies -<Block Inheritance> -<Block Inheritance>
+pmxStagePressure -Internals() : PStream -PipeInsulationCollection PipeSegment
+pmxStageHas2LiquidPhases -MSHEX -PipeSegment
-QManager -<Block Inheritance>
+pmxStageThermalEfficiency -PropertiesExt : Properties
-Pipeline
+pmxStageVaporTemperature +CalculateInternals() +InsertAfter()

«enumeration» «enumeration»
PipeInsulationCollection
pmxStageHardwareTypesEnum pmxPipeSegmentPropEnum
+pmxStageHardwareGeneral -Count
+pmxPSPipeLength
+pmxStageHardwareTray -Item : Properties
+pmxPSIncrement
+pmxStageHardwareRandomPacking -Pipeline
+pmxPSElevationChange
+pmxStageHardwareStructuredPacking -Project
+pmxPSAngle
+pmxPSNomSize
+pmxPSSchedule
+pmxPSAbsoluteRoughness
Properties +pmxPSHeatTransferCoeff
Properties +pmxPSAmbientTemp
+Count
+Count +pmxPSSinglePhaseFrictionFact
+Item : Base Property
+Item : Base Property +pmxPSMultiPhaseFlowCorr
+Parent
+Parent +pmxPSPressureDrop
+Project
+Project +pmxPSOutletPress
+pmxPSDeltaTemp
+pmxPSOutletTemp
+pmxPSTotalLiqHoldUp
«enumeration» +pmxPSHeatTransfer
pmxPSInsulationPropertiesEnum +pmxPSKinEChange
+pmxPSInsulationType +pmxPSPotEChange
+pmxPSInsulationThickness +pmxPSFluidEnthalpyChange
«enumeration»pmxOLGASPropEnum +pmxPSInsulationThermalConductivity +pmxPSCumulLengthTable
+pmxOLGAS_IWATER +pmxPSTempTable
+pmxOLGAS_XDROP1 +pmxPSPressTable
+pmxOLGAS_FWINV +pmxPSPressDropTable
+pmxOLGAS_IDUOILW +pmxPSFlowRegimeTable
+pmxOLGAS_DUOILW «enumeration» +pmxPSLiqHoldUpTable
+pmxOLGAS_IVISCL pmxPipelinePropEnum +pmxPSDPDLTable
+pmxOLGAS_USHT +pmxPipelineNumberOfSegments +pmxPSFricGradientTable
+pmxOLGAS_USW +pmxPipelinePipeLength +pmxPSElevationGradientTable
+pmxOLGAS_WAT +pmxPipelineHeatTransferCoeff +pmxPSReysNoTable
+pmxOLGAS_TAUG +pmxPipelineDeltaP +pmxPSFricFactorTable
+pmxOLGAS_TAUO +pmxPipelineOutletPress +pmxPSHeatXferTable
+pmxOLGAS_TAUW +pmxPipelineDeltaTemp +pmxPSLiqFlowTable
+pmxOLGAS_IDWH1 +pmxPipelineOutletTemp +pmxPSLiqVelTable
+pmxOLGAS_IDWH2 +pmxPipelineTotalLiqHoldUp +pmxPSLiqMWTable
+pmxOLGAS_IDWH3 +pmxPipelineElevationChange +pmxPSLiqDensTable
+pmxOLGAS_VISCHLEFF +pmxPipelineHeatTransfer +pmxPSLiqViscTable
+pmxOLGAS_VISCWTEFF +pmxPipelineKinEChange +pmxPSLiqSurfTensTable
+pmxOLGAS_WET_PER_OIL +pmxPipelinePotEChange +pmxPSGasFlowTable
+pmxOLGAS_WET_PER_WAT +pmxPipelineFluidEnthalpyChange +pmxPSGasVelTable
+pmxOLGAS_WET_PER_LIQ +pmxPipelineCumulLengthTable +pmxPSGasMWTable
+pmxOLGAS_WET_PER_LIQ_COLLAPSED +pmxPipelineTempTable +pmxPSGasDensTable
+pmxOLGAS_FRAC_OIL_IN_GAS +pmxPipelinePressTable +pmxPSGasViscTable
+pmxOLGAS_FRAC_WAT_IN_GAS +pmxPipelinePressDropTable +pmxPSSolutionMethod
+pmxOLGAS_DROP_VELOCITY +pmxPipelineFlowRegimeTable +pmxPSResistanceCoeff
+pmxOLGAS_MODEL +pmxPipelineLiqHoldUpTable +pmxPSTypeOfSegment
+pmxOLGAS_WC_C +pmxPipelineDPDLTable +pmxPSFittingType
+pmxOLGAS_WC_Model4 +pmxPipelineFricGradientTable +pmxPSInsideHTC
+pmxOLGAS_VISCMULT_Model4 +pmxPipelineElevationGradientTable +pmxPSWallID
+pmxOLGAS_WCTable +pmxPipelineReysNoTable +pmxPSWallThickness
+pmxOLGAS_VISCMULTTable +pmxPipelineFricFactorTable +pmxPSWallMatOfCon
+pmxOLGAS_TMDEGC +pmxPipelineHeatXferTable +pmxPSWallThermalConductivity
+pmxPipelineLiqFlowTable +pmxPSSurroundingsType
+pmxPipelineLiqVelTable +pmxPSGroundType
+pmxPipelineLiqMWTable +pmxPSGroundThermalConductivity
+pmxPipelineLiqDensTable +pmxPSBuriedDepth
Block Structure and +pmxPipelineLiqViscTable
+pmxPipelineLiqSurfTensTable
+pmxPSOutsideFluidVelocity
+pmxPSGroundDiffusivity
Properties Enums II +pmxPipelineGasFlowTable
+pmxPipelineGasVelTable
+pmxPSWellFlowTime
+pmxPSBeggsBrillRoughPipeOption

(Columns, Pipelines, +pmxPipelineGasMWTable


+pmxPipelineGasDensTable
+pmxPSBeggsBrillHoldupCorrection
+pmxPSDiameterNominal
+pmxPipelineGasViscTable +pmxPSWallOD 35
Recycles)
Block
+ConnectionsCount Reactor MSHEX
+EnergyConnections : QConnections
-<Block Inheritance> -Count
+Flowsheet
-Constraints -Item : SSHEX
+Inlets : PConnections
-ReactionSet -QManager
+Name
-Notes CRReactor +AddSSHEX() : SSHEX
+Outlets : PConnections -<Block Inheritance>
+Parent -Reactor
+Project -SSHex
+Properties : Base Property VLReactor CRHEX
+Status : Long
-<Reactor Inheritance> -<MSHEX Inheritance>
-TimeModified
-TimeSolved
+Type : pmxBlockTypesEnum
+VShape
+Clear()
+Delete()
+Solve()
HEXRating
«enumeration»
QManager -HEXType pmxHEXRPropertiesTypeEnum
-HEXRating -Notes
-Project +pmxHEXRPTResults
-Parent +pmxHEXRPTShell
-Project -QManager
-Properties(pmxHEXRPropertiesTypeEnum) : Properties +pmxHEXRPTTube
-Properties +pmxHEXRPTFin
-QTCurve : Curve -Sides : SSHEX
+pmxHEXRPTBaffle
-Status : Long +Solve() +pmxHEXRPTFinFan
+CreateHEXRating() : HEXRating +pmxHEXRPTCMPCore
+DeleteHEXRating() +pmxHEXRPTPFPack
+ExportHEXRating()
+ImportHEXRating()
+ReplaceHEXRating()
HEXRatingSides
Curve -Count
PTables -HEXRating
-AllowExtrapolation : Boolean
-Item : HEXRatingSide
-Data : PTables -Count
-Project
-Method : pmxCurveInterpEnum -Item : PDoubleTable
-Project : Amine Analysis Enums -Label
-XColumn : Long -Name
+AverageX() : PDouble -Parent
+AverageY() : PDouble -Project
-RowCount : Long Properties
+CalcX() : PDouble
HEXRatingSide +Count
+CalcY() : PDouble +Add() : PDoubleTable
+IsDataAvailable() : Boolean -CMPFinCollection* +Item : Base Property
-GeomSideProperties* : Properties +Parent
«enumeration»
-HEXRating +Project
pmxQManagerPropEnum
-PipeProperties : Properties
+pmxQMgrTotalEnergySupply -Project
«enumeration»
+pmxQMgrTotalEnergyDemand -Side : SSHEX
pmxCurveInterpEnum
+pmxQMgrTMaxSupply -SideProperties : Properties
+pmxMonotonicSpline +pmxQMgrTMinSupply
+pmxQuarticSpline +pmxQMgrTMaxDemand
+pmxLagrangeSpline +pmxQMgrTMinDemand
+pmxLinearSpline +pmxQMgrLMTD
+pmxQMgrEndUA PropertiesCollection
+pmxQMgrEndApproachT +Count «enumeration»
+pmxQMgrEMTD +Item : Properties pmxHEXRPipePropertiesEnum
+pmxQMgrEffUA +Parent +pmxHEXRPPInMainDia
+pmxQMgrEffApproachT +Project +pmxHEXRPPInMainStrLen
+Insert() : Properties +pmxHEXRPPInMainEquiLen
+pmxHEXRPPInNozStrLen
+pmxHEXRPPInNozPressDrop
«enumeration»
+pmxHEXRPPLiqDriHead
pmxHEXTypesEnum
Block Structure and +pmxHEXShellandTube
+pmxHEXRPPOutMainDia
+pmxHEXRPPOutMainStrLen
+pmxHEXDoublePipe +pmxHEXRPPOutMainEquiLen
Properties Enums III +pmxHEXFinFan
+pmxHEXCompact
+pmxHEXRPPOutNozStrLen
+pmxHEXRPPVertHtElbow
(HEXRating) +pmxHEXPlateFrame +pmxHEXRPPOutNozPressDrop
36
SSHEX Separator Stage
-<Block Inheritance> -<SSHEX Inheritance> -<Block Inheritance>
-Internals() : PStream -SizingProperties* -Column : StagedColumn
-MSHEX +DeleteSizingProperties() -HardwareProperties*(pmxStageHardwareTypesEnum) : Properties
-QManager -Internal : PStream
+CalculateInternals()

«enumeration» «enumeration» «enumeration»


pmxHEXRResultsPropertiesEnum pmxHEXRShellPropertiesEnum pmxHEXRFinPropertiesEnum
+pmxHEXRRPOverDesign +pmxHEXRSPID +pmxHEXRFPNumber
+pmxHEXRRPOverallHTC +pmxHEXRSPOrientation +pmxHEXRFPNumberPerTube
+pmxHEXRRPCleanHTC +pmxHEXRSPTubeSideEntry +pmxHEXRFPHeight
+pmxHEXRRPBareHTC +pmxHEXRSPNumParallel +pmxHEXRFPThickness
+pmxHEXRRPServiceHTC +pmxHEXRSPNumSeries +pmxHEXRFPGaugeThickness
+pmxHEXRRPAreaAvail +pmxHEXRSPNumSealingStripPairs +pmxHEXRFPRootDia
+pmxHEXRRPAreaReq +pmxHEXRSPTubesheetThick +pmxHEXRFinToTotArea
+pmxHEXRRPEffUA +pmxHEXRSPTEMAFront +pmxHEXRFPMatOfCon
+pmxHEXRRPEndPntUA +pmxHEXRSPTEMAShell
+pmxHEXRRPDuty +pmxHEXRSPTEMARear
+pmxHEXRRPEffMTD +pmxHEXRSPImpControl
+pmxHEXRRPFCorrFactor +pmxHEXRSPInNozzleDia «enumeration»
+pmxHEXRRPCMTD +pmxHEXRSPOutNozzleDia pmxHEXRBafflePropertiesEnum
+pmxHEXRRPVolume +pmxHEXRSPCalcImpContDevice +pmxHEXRBPCutOrient
+pmxHEXRRPDutyTbl +pmxHEXRSPNumPhasesEnt +pmxHEXRBPType
+pmxHEXRRPTubeTempTbl +pmxHEXRSPrho_v_2 +pmxHEXRBPInNozzleLoc
+pmxHEXRRPdTTbl +pmxHEXRSPBundleDia +pmxHEXRBPNumCrossPasses
+pmxHEXRRPTubeThCondTbl +pmxHEXRSPVoidFraction +pmxHEXRBPCut
+pmxHEXRRPMainHTCTbl +pmxHEXRBPThickness
+pmxHEXRBPLongLength
+pmxHEXRBPCentralSpacing
+pmxHEXRBPInletSpacing
«enumeration»pmxHEXRSidePropEnum +pmxHEXRBPOutletSpacing
«enumeration»
+pmxHEXRSideService pmxHEXRTubePropertiesEnum
+pmxHEXRSideHTC
+pmxHEXRTPOD
+pmxHEXRSideFoulResist «enumeration»
+pmxHEXRTPID
+pmxHEXRSideFoulThick pmxHEXRFinFanPropertiesEnum
+pmxHEXRTPThickness
+pmxHEXRSideFlowArea
+pmxHEXRTPGaugeThickness +pmxHEXRFFEntryType
+pmxHEXRSideEquilDiaDeltaP
+pmxHEXRTPPitchRatio +pmxHEXRFFFlowType
+pmxHEXRSideEquilDiaHTC
+pmxHEXRTPPitch +pmxHEXRFFTubeOrientation
+pmxHEXRSideFlowLen
+pmxHEXRTPLength +pmxHEXRFFNumBundlePerBay
+pmxHEXRSideSpecifiedPressureDrop
+pmxHEXRTPRoughness +pmxHEXRFFNumBayParallel
+pmxHEXRSideCalculatedPressureDrop
+pmxHEXRTPService +pmxHEXRFFNumInNozzPerBundle
+pmxHEXRSideInletPressureDrop
+pmxHEXRTPCount +pmxHEXRFFNumOutNozzPerBundle
+pmxHEXRSideInternalPressureDrop
+pmxHEXRTPMaxCount +pmxHEXRFFFanArrangement
+pmxHEXRSideOtherInternalPressureDrop
+pmxHEXRTPType +pmxHEXRFFNumFansPerBay
+pmxHEXRSideOutletPressureDrop
+pmxHEXRTPPattern +pmxHEXRFFFanDia
+pmxHEXRSideTemperatureTbl
+pmxHEXRTPInNozzleDia +pmxHEXRFFCombinedEff
+pmxHEXRSideLengthTbl
+pmxHEXRTPOutNozzleDia +pmxHEXRFFRadialFanTipClearance
+pmxHEXRSidePressureDropTbl
+pmxHEXRTPPasses +pmxHEXRFFTubeForm
+pmxHEXRSideHTRegimeTbl
+pmxHEXRTP1stTubePass +pmxHEXRFFNumTubeRows
+pmxHEXRSideHTCTbl
+pmxHEXRTPInsideCorrosionAllowance +pmxHEXRFFNumOddRows
+pmxHEXRSideVelocityTbl
+pmxHEXRTPOutsideCorrosionAllowance +pmxHEXRFFNumEvenRows
+pmxHEXRSideReNumTbl
+pmxHEXRTPJointWeldEff +pmxHEXRFFWidth
+pmxHEXRSidePrNumTbl
+pmxHEXRTPMatOfCon +pmxHEXRFFFanPower
+pmxHEXRSideLatentHeatTbl
+pmxHEXRTPMAWP +pmxHEXRFFFanAreaToBayArea
+pmxHEXRSideInletFlowLoc
+pmxHEXRTPVoidFraction +pmxHEXRFFDepth
+pmxHEXRSideOutletFlowLoc
+pmxHEXRTPReactionsInTube +pmxHEXRFFTotalFanPower
37
Block
+ConnectionsCount
CRReactor
+EnergyConnections : QConnections
Project +Flowsheet -<Block Inheritance>
-Calculators +Inlets : PConnections -Reactor
+EnergyBudgets +Name -SSHex
+Environments -Notes
+ExcelWorkbooks +Outlets : PConnections
+Flowsheets +Parent
+Name +Project
+Oils +Properties : Base Property
+Path Blocks +Status : Long
-Reactions -TimeModified
+Count
-ReactionSets -TimeSolved
+Flowsheet
+Recoveries +Type : pmxBlockTypesEnum
+Item : Block
-Solver +VShape
+Project
+SpeciesCache +Clear()
+SpeciesNames +Add() : Block ReactionSets
+Delete()
-UnitSet +Solve() -Count
-UserValueSets -Item : ReactionSet
+VisioDocument -Parent
+... -Project
+ClearAllCalculated() Environment +Add() : ReactionSet
+Close() -Components +Remove()
+Save() -FlashOptions
+SaveAs() -GEModelEvalTemperature : PDouble
-FreezeFormationDeltaT : PDouble
Environments -ModelParameters
+Count +Name
+Item : Environment -Notes
+Project +Project
+Add() : Environment +PhysProp
Components +PhysPropMethodSet
-PoyntingIntervals : PLong
+Count RxnKeqSet
-ReactionSets
+Environmnent
-RxnKeqSet -Count
+InstalledOils : Oils
+Copy() -Item : RxnKeq
+Item : Component
+CreatePhysProp() -Environment
+Project
+Delete() -Project
+Add() : Component
+Edit() +Add() : RxnKeq
+Remove()
+Remove()
+Reorder()
+SetItems()
+SetItems()

FlashOptions ModelParameters PhysProp


-AllowPseudoSolutions : Boolean -BinaryInteractions() +Components()
-Environment -ChienNullParameters +Environment
-FlashAlgorithms() : pmxFlashAlgEnum -Project +CalcBinary() : Double
-InitialGuessAlgorithm : pmxFlashIGEnum -PureParameters() +CalcBinary_dT() : Double
-Project -UNIFAQParameters +CalcComponent()
-PhaseTolerance : PDouble +CalcComponent_dT()
-UseShahVLEFirst : Boolean +CalcInterphase() : Double
+CalcInterphase_dT() : Double
+CalcMixture() : Double
+CalcMixture_dT() : Double
+CalcPure() : Double
+CalcPure_dT() : Double
+ReloadAllProperties()

PhysPropMethod PhysPropMethodSet RxnKeq


-CATID : String -Environment -Exponents : Double
-Description : String -Item : PhysPropMethod -NumberOfSpecies : Long
-ID : Long -Notes -Phases : pmxPhaseEnum
-Label -Project
RxnKeqName -Project
-Name -StabilityObject : PhysPropMethod -RxnKeqName
-Parent +GetPackageNames() -Classification : String -SpeciesName()
-ProgID : String +GetPhasePackageNames() -ID : Long -StoichCoeff : Double
-Project +LoadPackage() -Name
+LoadPhasePackage() -Project

38
VLReactor Environment and
-<Reactor Inheritance>
Reactive
Reactor
ReactorConstraint
-<Block Inheritance>
-Constraints -Component
ReactorConstraints -Name
-ReactionSet
-Count -Project
-Item : ReactorConstraint -Properties
-Project -Reactor
-Reactor -Status : Long
ReactionSet +Add() : ReactorConstraint -SupportedComponents() : Component
-Count -Type : pmxReactorConstraintEnum
-Item : Reaction +Delete()
-Name
-Notes
«enumeration»
-Parent
pmxReactorConstraintEnum
-Project
-Type : Long +pmxRCLinear
+pmxRCFischer1974
+Add() : Reaction EquationContainer +pmxRCNSERC1993
+Delete()
-Equation +pmxRCLuinstradHaene
+Remove()
-Name +pmxRCNSERC2002
-Parent +pmxRCQuenchTemperature
-Project +pmxRCQuenchInletOffsetTemperature
-Properites
-VariableUnitsEnum : pmxUnitsEnum
-VariableUnitsIndex : Long
Reaction «enumeration»
-ConversionEquation Equation pmxReactorConstraintPropEnum
-EquilibriumConstant +pmxReactorConstraintNumParms
-EquationID : String
-ForwardRateConstant +pmxReactorConstraintActive
-FirstDerivative : Double
-Name +pmxReactorConstraintParm1
-Function : Double
-Notes RateConstant +pmxReactorConstraintParm2
-HighDataLimit : Double
-Project
-Equation -HighLimit : Double
-Properties : Properties
-Name -Integral : Double
-RateDenoms
-Parent -IntegralFOverX : Double
-ReactionComponents
-Project -IsValidRange : Boolean
-ReverseRateConstant
-Properties -IsTypicalUse : Boolean
+Delete() -VariableUnitsEnum : pmxUnitsEnum -LowDataLimit : Double
+Open() : Reaction -VariableUnitsIndex : Long -LowLimit : Double
+Original() : Reaction -Parameters() : Double
+Update() -SecondDerivative : Double
-SingleRoot : Double
-ParameterCount : Long

RateDenoms RateDenom
-Count -Name
-Item : RateDenom -Project
-Project -Properties
-Reaction -Reaction
+Add() : RateDenom +Delete()
+Remove() +Equation()

SpeciesName
ReactionComponents +CASRN : Long
-Count ReactionComponent +Charge : Long
-Item : ReactionComponent -SpeciesName -ElementalMakeup : String
-Project -Project +Formula : String
-Reaction -Properties +Name : String
+Add() : ReactionComponent -Reaction +PrimaryName : String
+Remove() +Delete() -Project
+SetItems() -...

39
Project (Detail)
+Azeotropes
-Calculators
Additional Project Objects +Constant(pmxConstantsEnum) : PDouble
-DisplayedCompositionBases() : pmxCompositionEnum
+EnergyBudgets
+Environments
+ExcelWorkbooks
+Flowsheets
-IncludeMixedLiquidPhase : Boolean
-InfDilActCoeffs
-LastSaveVersion
-Limit : PDouble
-MatOfConCollection
UserValueSets -ModelParameters
-MsgLog
-Count +Name
-Item : UserValueSet +Oils
-Project +Path
+Add() : UserValueSet -PStreamPropMethodSet
-Reactions
-ReactionSets
+Recoveries
UserValueSet UnitSet
UnitsCollection -RecycleOptions
-Count -FractionAsPercentage : Boolean -RxnKeqNames
-Name -Count +SpeciesCache
-Item : UserValue
-PressureInGauge : Boolean -Item : Units +SpeciesNames
-Name
-Notes -Project -Solver
-Project +GetExternalUnits(pmxUnitsEnum)() : String -Tolerance : PDouble
+Add() : UserValue +GetInternalUnits(pmxUnitsEnum)() : String -UnitsCollection
+GetNames(String())() -UnitSet
Units -UserValueSets
-Viewer
-BaseUnits : String +VisioDocument
-Factor : Double
UserValue «enumeration» +ClearAllCalculated()
-LongName : String
pmxUserValuePropEnum +Close()
-Calculator -Offset : Double
+pmxUserValueParameter +CreateEquation()
-Name -Units : String
+pmxUserValueLowerBound +CreateObject()
-Project
+pmxUserValueUpperBound +EditOptions()
-Properties
+pmxUserValueEnforceBounds +GetInternalUnits() : String
-UserValueSet
+Save()
+Delete() +SaveAs()
+WarningText() : String

ReactionSets Reactions
-Count -Count
-Item : ReactionSet -Item : Reaction
-Parent -Notes
-Project -Project
PStreamPropMethodSet +Add() : ReactionSet +Add() : Reaction RxnKeqNames
+Remove() +Remove()
-Count -Count
-Item : PStreamPropMethod -Item : RxnKeqName
-Project -Project

Reaction
-ConversionEquation
ReactionSet -EquilibriumConstant
PStreamPropMethod ModelParameters
-Count -ForwardRateConstant RxnKeqName
-CATID : String -BinaryInteractions()
-Item : Reaction -Name
-Description : String -Classification : String -ChienNullParameters
-Name -Notes
-ID : Long -ID : Long -Project
-Notes -Project
-Label -Name -PureParameters()
-Parent -Properties : Properties
-Name -Project -UNIFAQParameters
-Project -RateDenoms
-Parent -Type : Long -ReactionComponents
-ProgID : String -ReverseRateConstant
+Add() : Reaction
-Project
+Delete() +Delete()
+Remove() +Open() : Reaction
40 +Original() : Reaction
+Update()
HeatBudget
-Blocks() : Block
-DataSource : pmxEnergyBudgetDataSourceEnum
-Flowsheet
-HeatBudget : Boolean
«enumeration» -Name
pmxToleranceEnum -Notes
+pmxInnerPhysPropTol -Properties
«enumeration» -Status : Long
+pmxOuterPhysPropTol
pmxConstantsEnum -System : Boolean
+pmxInnerFlashTol
+pmxOuterFlashTol +pmxPi +Calculate() : Boolean
+pmxBlockTol +pmxMolarGasConstant +SetDataSource()
+pmxRecycleTol +pmxBoltzmannConstant
+pmxPlanckConstant
+pmxAvogadroConstant
«enumeration»
+pmxFaradayConstant
pmxHeatBudgetPropertyEnum
+pmxSpeedOfLight
+pmxElementaryCharge +pmxHeatBudgetNetDuty
+pmxBohrRadius +pmxHeatBudgetGrossHeatOut
+pmxStefanBoltzmannConstant +pmxHeatBudgetGrossHeatIn
+pmxAtomicMassConstant +pmxHeatBudgetHeat
+pmxAtmPressure +pmxHeatBudgetTMax
+pmxIGRefPressure +pmxHeatBudgetTMin
+pmxIGRefTemperature
+pmxIGRefVolume
+pmxLiqRefTemperature
+pmxAccelGravity
«enumeration»
pmxEnergyBudgetDataSourceEnum
+pmxEBDSProject
+pmxEBDSFlowsheet
EnergyBudgets
+pmxEBDSUserSelection
-Count
-Item : HeatBudget
-Project
+AddHeatBudget() : HeatBudget
+AddPowerBudget() : PowerBudget PowerBudget
-Blocks() : Block
-DataSource : pmxEnergyBudgetDataSourceEnum
-Flowsheet
-HeatBudget : Boolean
Recoveries -Name
-Count -Notes
-Item : Recovery -Properties
-Project -Status : Long
-System : Boolean
+Add() : Recovery
+Calculate() : Boolean
+SetDataSource()

«enumeration»
Recovery pmxPowerBudgetPropertyEnum
-Name +pmxPowerBudgetNetPower
-Notes +pmxPowerBudgetGrossPowerOut
-Properties +pmxPowerBudgetGrossPowerIn
-RecoveryDataSource : pmxRecoveryDataSourceEnum +pmxPowerBudgetPower
-RecoveryFlowsheet : Flowsheet +pmxPowerBudgetPRatio
-RecoveryPStreams() : PStream +pmxPowerBudgetDeltaP
-SpeciesList : Species +pmxPowerBudgetHead
-Status : Long
-System : Boolean
-ReferenceDataSource : pmxRecoveryDataSourceEnum
-ReferenceFlowsheet : Flowsheet
-ReferencePStreams : PStream
+Calculate() : Boolean
+SetRecoveryDataSource()
+SetReferenceDataSource() «enumeration» «enumeration»
pmxRecoveryDataSourceEnum pmxRecoveryPropertyEnum
+pmxRDSProjectInlets +pmxRecoveryCompBasis
+pmxRDSProjectOutlets +pmxRecoveryRatio
+pmxRDSFlowsheetInlets +pmxRecoveryAtomicBasis
+pmxRDSFlowsheetOutlets +pmxRecoverySummationOnly
+pmxRDSUserSelection +pmxRecoveryFirstPStream
41
Block Properties
«enumeration» «enumeration» «enumeration»
pmxPipelinePropEnum pmxStagedColumnPropEnum pmxPipeSegmentPropEnum
+pmxPipelineNumberOfSegments +pmxStagedColumnIdealStages +pmxPSPipeLength
+pmxPipelinePipeLength +pmxStagedColumnNumberTopDown +pmxPSIncrement
+pmxPipelineHeatTransferCoeff +pmxStagedColumnFlashType +pmxPSElevationChange
+pmxPipelineDeltaP +pmxStagedColumnEfficiencyPhase +pmxPSAngle
+pmxPipelineOutletPress +pmxStagedColumnIterations +pmxPSNomSize
+pmxPipelineDeltaTemp +pmxStagedColumnUseLastSolution +pmxPSSchedule
+pmxPipelineOutletTemp +pmxStagedColumnAddOns +pmxPSAbsoluteRoughness
+pmxPipelineTotalLiqHoldUp +pmxStagedColumnDegreesOfFreedom +pmxPSHeatTransferCoeff
+pmxPipelineElevationChange +pmxStagedColumnBostonSullivanKb +pmxPSAmbientTemp
+pmxPipelineHeatTransfer +pmxStagedColumnMainLiquidPhase +pmxPSSinglePhaseFrictionFact
+pmxPipelineKinEChange +pmxStagedColumnPressureDrop +pmxPSMultiPhaseFlowCorr
+pmxPipelinePotEChange +pmxStagedColumnType +pmxPSPressureDrop
+pmxPipelineFluidEnthalpyChange +pmxStagedColumnKDamping +pmxPSOutletPress
+pmxPipelineCumulLengthTable +pmxStagedColumnCondenser3Phases +pmxPSDeltaTemp
+pmxPipelineTempTable +pmxStagedColumnReboiler3Phases +pmxPSOutletTemp
+pmxPipelinePressTable +pmxStagedColumnEnthalpyModel +pmxPSTotalLiqHoldUp
+pmxPipelinePressDropTable +pmxStagedColumnMaxInitIters +pmxPSHeatTransfer
+pmxPipelineFlowRegimeTable +pmxStagedColumnThermalEff +pmxPSKinEChange
+pmxPipelineLiqHoldUpTable +pmxStagedColumnCalculateHydraulics +pmxPSPotEChange
+pmxPipelineDPDLTable +pmxStagedColumnInnerLoopModel +pmxPSFluidEnthalpyChange
+pmxPipelineFricGradientTable +pmxStagedColumnPhaseThreshold +pmxPSCumulLengthTable
+pmxPipelineElevationGradientTable +pmxPSTempTable
+pmxPipelineReysNoTable +pmxPSPressTable
+pmxPipelineFricFactorTable +pmxPSPressDropTable
«enumeration»
+pmxPipelineHeatXferTable +pmxPSFlowRegimeTable
pmxStagePropEnum
+pmxPipelineLiqFlowTable +pmxPSLiqHoldUpTable
+pmxPipelineLiqVelTable +pmxStageMurphreeEfficiencies +pmxPSDPDLTable
+pmxPipelineLiqMWTable +pmxStagePressure +pmxPSFricGradientTable
+pmxPipelineLiqDensTable +pmxStageHas2LiquidPhases +pmxPSElevationGradientTable
+pmxPipelineLiqViscTable +pmxStageThermalEfficiency +pmxPSReysNoTable
+pmxPipelineLiqSurfTensTable +pmxStageVaporTemperature +pmxPSFricFactorTable
+pmxPipelineGasFlowTable +pmxPSHeatXferTable
+pmxPipelineGasVelTable +pmxPSLiqFlowTable
+pmxPipelineGasMWTable «enumeration» +pmxPSLiqVelTable
+pmxPipelineGasDensTable pmxPumpPropEnum +pmxPSLiqMWTable
+pmxPipelineGasViscTable +pmxPumpDeltaP +pmxPSLiqDensTable
+pmxPumpEfficiency +pmxPSLiqViscTable
+pmxPumpHead +pmxPSLiqSurfTensTable
«enumeration» +pmxPumpPower +pmxPSGasFlowTable
pmxSaturatorPropEnum +pmxPSGasVelTable
+pmxPSGasMWTable
+pmxSaturatorFraction
+pmxPSGasDensTable
+pmxSaturatorTemperature «enumeration»
+pmxPSGasViscTable
+pmxSaturatorPressure pmxReactorPropEnum
+pmxPSSolutionMethod
+pmxSaturatorDeltaP +pmxReactorDeltaP +pmxPSResistanceCoeff
+pmxSaturatorDeltaT +pmxReactorDuty +pmxPSTypeOfSegment
+pmxSaturatorDeltaSatP +pmxReactorConversion +pmxPSFittingType
+pmxReactorPFRSolutionMethod +pmxPSInsideHTC
+pmxReactorMaxPhases +pmxPSWallID
«enumeration» +pmxReactorYield +pmxPSWallThickness
pmxSSHEXPropEnum +pmxReactorIVMethod +pmxPSWallMatOfCon
+pmxSSHEXPDrop +pmxReactorBypassFraction +pmxPSWallThermalConductivity
+pmxSSHEXDeltaT +pmxReactorMaxAvailableConstraints +pmxPSSurroundingsType
+pmxSSHEXDuty +pmxReactorIncrements +pmxPSGroundType
+pmxSSHEXCurveType +pmxReactorGibbsSet +pmxPSGroundThermalConductivity
+pmxSSHEXCurveIncrements +pmxReactorType +pmxPSBuriedDepth
+pmxReactorIncrementType +pmxPSOutsideFluidVelocity
+pmxReactorReactionExtent +pmxPSGroundDiffusivity
+pmxReactorReactionConversion +pmxPSWellFlowTime
«enumeration» +pmxReactorYieldComponent +pmxPSBeggsBrillRoughPipeOption
pmxSeparatorPropEnum +pmxReactorGibbsReactive +pmxPSBeggsBrillHoldupCorrection
+pmxSeparatorPDrop +pmxReactorMaxTemperature +pmxPSDiameterNominal
+pmxSeparatorFracVapor +pmxReactorDeltaT +pmxPSWallOD
+pmxSeparatorDuty +pmxReactorFracVapor
+pmxSeparatorCurveType +pmxReactorFracLLiquid
+pmxSeparatorCurveIncrements +pmxReactorFracHLiquid
+pmxSeparatorSingleLiquidPhase +pmxReactorSegments
+pmxSeparatorFracLLiquid +pmxReactorDeltaPMethod
+pmxSeparatorFracHLiquid +pmxReactorParticleDiameter
+pmxReactorNEQMassTransfer

42
Units
Block Enums
Enumerators
«enumeration» «enumeration» «enumeration» «enumeration»
pmxBlockTypesEnum pmxCompExpPropEnum pmxUnitsEnum pmxUnitsEnum
+pmxCompExpBlock +pmxCompExpAdiabaticEff +pmxUnrecognizedUnit +pmxMolarEntropyUnit
+pmxCRHEXBlock +pmxCompExpAdiabaticHead +pmxUnknownUnit +pmxMassEntropyUnit
+pmxDividerBlock +pmxCompExpPolytropicEff +pmxDimensionlessUnit +pmxVolumeFlowUnit
+pmxJTValveBlock +pmxCompExpPolytropicHead +pmxTimeUnit +pmxStdVapVolFlowUnit
+pmxMakeupBlock +pmxCompExpDeltaP +pmxLengthUnit +pmxNormalVapVolFlowUnit
+pmxMixerSplitterBlock +pmxCompExpPRatio +pmxMassUnit +pmxStdLiqVolFlowUnit
+pmxMSHEXBlock +pmxCompExpSpeed +pmxMoleUnit +pmxDiffusivityUnit
+pmxPipelineBlock +pmxCompExpPower +pmxMassFlowUnit +pmxHeatTransCoeffUnit
+pmxPipeSegmentBlock +pmxCompExpIsentropicK +pmxMolarFlowUnit +pmxHeatTransResistUnit
+pmxPumpBlock +pmxCompExpPolytropicN +pmxForceUnit +pmxHeatFluxUnit
+pmxRecycleBlock +pmxMomentumUnit +pmxHeatTransUAUnit
+pmxSaturatorBlock +pmxAreaUnit +pmxMassTransCoeffUnit
+pmxSeparatorBlock +pmxRecipLengthUnit +pmxMassFluxUnit
+pmxSSHEXBlock +pmxFrequencyUnit +pmxSurfaceTensionUnit
+pmxStageBlock «enumeration» +pmxVelocityUnit +pmxDipoleMomentUnit
+pmxStagedColumnBlock pmxDividerEnum +pmxAccelerationUnit +pmxElecChargeUnit
+pmxXFSConnectorBlock +pmxAngleUnit +pmxIonicStrengthUnit
+pmxDividerFractionExtracted
+pmxQRecycleBlock +pmxAngVelUnit +pmxStokesLawConstUnit
+pmxDividerBulkDeltaP
+pmxReactorBlock +pmxAngAccelUnit +pmxFractionUnit
+pmxDividerBulkDeltaT
+pmxCRReactorBlock +pmxMoleWeightUnit +pmxASTMSlopeUnit
+pmxDividerExtractDeltaP
+pmxVLReactorBlock +pmxMolarConcentrationUnit +pmxIGHeatValueUnit
+pmxDividerExtractDeltaT
+pmxNEQReactorBlock +pmxMassConcentrationUnit +pmxLiquidHeatValueUnit
+pmxTemperatureUnit +pmxStressUnit
+pmxAbsTemperatureUnit +pmxLinExpCoefUnit
+pmxDeltaTempUnit +pmxElasticModUnit
«enumeration» +pmxRecipTempUnit +pmxMolarAreaUnit
«enumeration» pmxSplitterPropEnum +pmxPressureUnit +pmxSolubilityParamUnit
pmxJTValvePropEnum +pmxAbsPressureUnit +pmxInverseMolesUnit
+pmxSplitterPDrop
+pmxDeltaPresUnit +pmxMolarGasConstantUnit
+pmxJTValvePDrop
+pmxLinearDeltaPUnit +pmxBoltzmannConstantUnit
+pmxJTValveJTCoefficient
+pmxVolumeUnit +pmxPlanckConstantUnit
+pmxMolarVolumeUnit +pmxFaradayConstantUnit
+pmxMassVolumeUnit +pmxStefanBoltzmannConstantUnit
«enumeration» +pmxMolarDensityUnit +pmxVacuumPermeabilityUnit
«enumeration» pmxXFSConnectorEnum +pmxMassDensityUnit +pmxVacuumPermittivityUnit
pmxMakeupPropEnum +pmxXFSThreshold +pmxDynViscosityUnit +pmxJTCoefficientUnit
+pmxMakeupPDrop +pmxXFSTransferProperty1 +pmxKinViscosityUnit +pmxMolarEntropyByTempUnit
+pmxMakeupBulkBasis +pmxXFSTransferProperty2 +pmxThermalCondUnit +pmxMolalityConcentrationUnit
+pmxMakeupDesiredOutletBasis +pmxXFSInletTemperature +pmxMolarHeatCapUnit +pmxVolumetricLoadingUnit
+pmxMakeupBulk +pmxXFSInletPressure +pmxMassHeatCapUnit +pmxColumnCapacityFactorUnit
+pmxMakeupDesiredOutlet +pmxXFSInletVaporFraction +pmxEnergyUnit +pmxColumnFFactorUnit
+pmxXFSInletMassEnthalpy +pmxEnergyFlowUnit +pmxColumnLiquidLoadUnit
+pmxXFSOutletTemperature +pmxPowerUnit +pmxColumnLinearHoldupTimeUnit
+pmxXFSOutletPressure +pmxMolarEnergyUnit +pmxMolarReactionRateUnit
+pmxXFSOutletVaporFraction +pmxMassEnergyUnit +pmxCatalyticReactionRateUnit
+pmxXFSOutletMassEnthalpy +pmxEntropyUnit +pmxMolarConcUnit
«enumeration» +pmxXFSDeltaTemperature +pmxEntropyFlowUnit +pmxMassConcUnit
pmxQRecyclePropEnum +pmxXFSDeltaPressure
+pmxQRecycleError +pmxXFSDeltaVaporFraction
+pmxQRecycleCalculatedValue +pmxXFSDeltaMassEnthalpy
+pmxXFSTemperatureTol
+pmxXFSPressureTol
+pmxXFSVaporFractionTol
+pmxXFSMassEnthalpyTol

«enumeration»
pmxRecyclePropEnum
+pmxRecycleError
+pmxRecycleIterations
+pmxRecyclePriority
+pmxRecycleFunction
Enumerators by Use I
+pmxRecycleCalculate
+pmxRecycleWeights

43
Column Hardware
«enumeration» «enumeration» «enumeration»
pmxTrayHardwarePropEnum pmxStageGeneralHardwarePropEnum pmxStructuredPackingTypesEnum
+pmxTrayHardwareSpacing +pmxStageHardwareType +pmxStructPackUserDefined
+pmxTrayHardwareFractionActiveArea +pmxStageDiameter +pmxStructPackSulzer_BX
+pmxTrayHardwareWeirHeight +pmxStageFractionFlooding +pmxStructPackSulzer_BXPFP
+pmxTrayHardwareNumberOfPasses +pmxStageSystemLimitFlood +pmxStructPackSulzer_CY
+pmxTrayHardwareFrothModel +pmxStageSystemFactor +pmxStructPackSulzer_MC350_Y
+pmxTrayHardwareMassTransferModel +pmxStageInterfacialArea +pmxStructPackSulzer_MG64
+pmxTrayHardwareFloodingModel +pmxStageResidenceTime +pmxStructPackSulzer_MG90
+pmxTrayHardwareFrothGravity +pmxStageRealToIdealStages +pmxStructPackSulzer_M2X
+pmxTrayHardwareHeightOverWeir +pmxStageLiquidDiffusivity +pmxStructPackSulzer_M2Y
+pmxTrayHardwareFrothHeight +pmxStageVaporDiffusivity +pmxStructPackSulzer_M64_X
+pmxTrayHardwareFractionHoleArea +pmxStageLiquidMassTransferCoeff +pmxStructPackSulzer_M64_Y
+pmxTrayHardwareHoleDiameter +pmxStageVaporMassTransferCoeff +pmxStructPackSulzer_M125_X
+pmxTrayHardwareWeirSideWidth +pmxStageFlowParameter +pmxStructPackSulzer_M125_Y
+pmxTrayHardwareWeirCenterWidth +pmxStageCsFactor +pmxStructPackSulzer_M170_X
+pmxTrayHardwareWeirOffCenterWidth +pmxStageFsFactor +pmxStructPackSulzer_M170_Y
+pmxStageLiquidLoad +pmxStructPackSulzer_M250_X
+pmxStructPackSulzer_M250_Y
«enumeration» +pmxStructPackSulzer_M350_X
pmxRandomPackingTypesEnum +pmxStructPackSulzer_M350_Y
«enumeration» +pmxStructPackSulzer_M500_X
+pmxRandomPackUserDefined pmxStructuredPackingPropEnum +pmxStructPackSulzer_M500_Y
+pmxRandomPackBerlSaddles
+pmxStructuredPackingName +pmxStructPackSulzer_M750_Y
+pmxRandomPackCascadeMiniRings
+pmxStructuredPackingMassTransferModel +pmxStructPackSulzer_OF_C_36
+pmxRandomPackIntalox
+pmxStructuredPackingFloodingModel +pmxStructPackSulzer_N125_Y
+pmxRandomPackPallRings
+pmxStructuredPackingStageHeight +pmxStructPackSulzer_N250_X
+pmxRandomPackRaschigRings
+pmxStructuredPackingPressureDrop +pmxStructPackSulzer_N250_Y
+pmxRandomPackSuperIntalox
+pmxStructuredPackingHoldup +pmxStructPackSulzer_MG64_Y
+pmxRandomPackTellerettes
+pmxStructuredPackingLinearHoldupTime +pmxStructPackSulzer_MG40_Y
+pmxRandomPackNutterRings
+pmxStructPackSulzer_M202_Y
+pmxStructPackSulzer_M252_Y
+pmxStructPackSulzer_M452_Y
«enumeration» +pmxStructPackSulzer_M752_Y
«enumeration»
pmxPackingMaterialTypesEnum +pmxStructPackSulzer_MC250_Y
pmxRandomPackingPropEnum
+pmxPackingMaterialMetal +pmxStructPackSulzer_BXPlus
+pmxRandomPackingName
+pmxPackingMaterialPolyethylene +pmxRandomPackingMassTransferModel
+pmxPackingMaterialPVC +pmxRandomPackingFloodingModel
+pmxPackingMaterialPlastic +pmxRandomPackingStageHeight «enumeration»
+pmxPackingMaterialCeramic +pmxRandomPackingPressureDrop pmxStageHardwareTypesEnum
+pmxPackingMaterialGlass +pmxRandomPackingHoldup +pmxStageHardwareGeneral
+pmxPackingMaterialCarbon +pmxRandomPackingLinearHoldupTime +pmxStageHardwareTray
+pmxPackingMaterialParaffin
+pmxStageHardwareRandomPacking
+pmxStageHardwareStructuredPacking

Specifications and Constraints

«enumeration»
pmxStagedColumnSpecificationPropEnum
+pmxStagedColumnSpecificationTarget
+pmxStagedColumnSpecificationTolerance
+pmxStagedColumnSpecificationEstimate
+pmxStagedColumnSpecificationActive
+pmxStagedColumnSpecificationCalculatedValue
+pmxStagedColumnSpecificationWeighting
+pmxStagedColumnSpecificationType
+pmxStagedColumnSpecificationBasis
Enumerators by Use II
+pmxStagedColumnSpecificationUpperBound
+pmxStagedColumnSpecificationLowerBound
+pmxStagedColumnSpecificationFracX
+pmxStagedColumnSpecificationFracY

44
Separator Sizing Single Oils
«enumeration» «enumeration» «enumeration»
pmxSeparatorSizingPropEnum pmxSeparatorSizingPropEnum pmxOilPropEnum
+pmxSepSzType +pmxSepSzMAWP +pmxOilVABP
+pmxSepSzVapLiqDroplet +pmxSepSzCorrosionAllowance +pmxOilMW
+pmxSepSzVapLiqKFactor +pmxSepSzShellMatOfCon +pmxOilSG
+pmxSepSzVapTermVel +pmxSepSzShellThickness +pmxOilAPIGravity
+pmxSepSzLiqLiqDroplet +pmxSepSzShellJointWeldEff +pmxOilTc
+pmxSepSzLiqLiqCStar +pmxSepSzHeadType +pmxOilPc
+pmxSepSzLLiqTermVel +pmxSepSzHeadMatOfCon +pmxOilVc
+pmxSepSzHLiqTermVel +pmxSepSzHeadThickness +pmxOilAcentric
+pmxSepSzLLiqHoldupTime +pmxSepSzHeadJointWeldEff +pmxOilCHRatio
+pmxSepSzLLiqHoldupVolume +pmxSepSzBootShellMatOfCon +pmxOilRefIndex
+pmxSepSzLLiqHoldupDepth +pmxSepSzBootShellThickness +pmxOilLowTForViscosity
+pmxSepSzLLiqSurgeTime +pmxSepSzBootShellJointWeldEff +pmxOilViscosityAtLowT
+pmxSepSzLLiqSurgeVolume +pmxSepSzBootHeadType +pmxOilHighTForViscosity
+pmxSepSzLLiqSurgeDepth +pmxSepSzBootHeadMatOfCon +pmxOilViscosityAtHighT
+pmxSepSzLLiqLowLiquidShutdownDepth +pmxSepSzBootHeadThickness +pmxOilWatsonK
+pmxSepSzHLiqHoldupTime +pmxSepSzBootHeadJointWeldEff +pmxOil1090Slope
+pmxSepSzHLiqHoldupVolume +pmxSepSzDiameter +pmxOilD93FlashPt
+pmxSepSzHLiqHoldupDepth +pmxSepSzShellHeight +pmxOilPourPt
+pmxSepSzHLiqSurgeTime +pmxSepSzShellLength +pmxOilParaffinicFrac
+pmxSepSzHLiqSurgeVolume +pmxSepSzLDRatio +pmxOilNaphthenicFrac
+pmxSepSzHLiqSurgeDepth +pmxSepSzTotalHeight +pmxOilAromaticFrac
+pmxSepSzHLiqLowLiquidShutdownDepth +pmxSepSzTotalLength +pmxOilIGCp
+pmxSepSzSurgeBelowWeir +pmxSepSzBootDiameter
+pmxSepSzDemisterThick +pmxSepSzBootShellLength
+pmxSepSzDemisterClearance +pmxSepSzBootTotalLength
+pmxSepSzMinVapDisengageDepth +pmxSepSzFeedDistanceAboveSurge
+pmxSepSzVapDisengageDepth +pmxSepSzLLiqSettlingDepth
+pmxSepSzFeedNozzleDiameter +pmxSepSzHLiqSettlingDepth
+pmxSepSzVapNozzleDiameter +pmxSepSzLLiqBootDepth
+pmxSepSzLLiqNozzleDiameter +pmxSepSzSettlingLength
+pmxSepSzHLiqNozzleDiameter +pmxSepSzLLiqWeirHeight
+pmxSepSzMinLDRatio +pmxSepSzLLiqBucketLength
+pmxSepSzMaxLDRatio +pmxSepSzLLiqBucketBottom
+pmxSepSzLLiqResTime +pmxSepSzBucketGap
+pmxSepSzHLiqResTime +pmxSepSzHLiqWeirHeight
+pmxSepSzBaffle +pmxSepSzHLiqBucketLength
+pmxSepSzBaffleCut +pmxSepSzVolume
+pmxSepSzLiquidAboveBaffle +pmxSepSzMass
+pmxSepSzDesignTemperature +pmxSepSzMassWater
+pmxSepSzDiameterRounding

Compact Rating
«enumeration» «enumeration»
«enumeration» pmxHEXRCMPResultsPropertiesEnum
pmxHEXRCMPCorePropertiesEnum
pmxHEXRCMPSideGeomPropertiesEnum
+pmxHEXRCMPCPCoreWidth +pmxHEXRCMPRPOverDesign
+pmxHEXRCMPSGSymbol +pmxHEXRCMPRPLengthAvail
+pmxHEXRCMPCPCoreLength
+pmxHEXRCMPSGFinHeight +pmxHEXRCMPRPLengthReq
+pmxHEXRCMPCPCoreHeight
+pmxHEXRCMPSGInletHeader +pmxHEXRCMPRPCleanLengthReq
+pmxHEXRCMPCPOutThickness
+pmxHEXRCMPSGInletNozzle +pmxHEXRCMPRPDuty
+pmxHEXRCMPCPPSThickness
+pmxHEXRCMPSGInletLocation +pmxHEXRCMPRPEffMTD
+pmxHEXRCMPCPNumSeries
+pmxHEXRCMPSGOutletHeader +pmxHEXRCMPRPFCorrFactor
+pmxHEXRCMPCPNumParallel
+pmxHEXRCMPSGOutletNozzle +pmxHEXRCMPRPCMTD
+pmxHEXRCMPCPMatOfCon
+pmxHEXRCMPSGOutletLocation +pmxHEXRCMPRPVolume
+pmxHEXRCMPCPLayerArr
+pmxHEXRCMPSGEdgeBarWidth +pmxHEXRCMPRPDutyTbl
+pmxHEXRCMPCPNumLayer
+pmxHEXRCMPSGPassageLength +pmxHEXRCMPRPWallTempTbl
+pmxHEXRCMPCPExpandedString
+pmxHEXRCMPSGNumberLayers +pmxHEXRCMPRPWallThCondTbl
+pmxHEXRCMPSGEffLayerWidth +pmxHEXRCMPRPdTTbl
+pmxHEXRCMPSGBankingFactor
+pmxHEXRCMPSGInDistributionWidth
«enumeration»
+pmxHEXRCMPSGInDistributionLength
pmxHEXRCMPFinPropertiesEnum
+pmxHEXRCMPSGOutDistributionWidth «enumeration»
+pmxHEXRCMPSGOutDistributionLength +pmxHEXRCMPFPType pmxReactorConstraintEnum
+pmxHEXRCMPSGStackArr +pmxHEXRCMPFPThickness
+pmxRCLinear
+pmxHEXRCMPFPSpacing
+pmxRCFischer1974
+pmxHEXRCMPFPLength
+pmxRCNSERC1993
+pmxHEXRCMPFPPerforationFraction
+pmxRCLuinstradHaene
+pmxHEXRCMPFPHeatTransferArea
+pmxRCNSERC2002
+pmxHEXRCMPFPFreeFlowArea
+pmxRCQuenchTemperature
+pmxHEXRCMPFPHydDiam
+pmxRCQuenchInletOffsetTemperature

45
Reactors and Reactions Calculators
«enumeration» «enumeration» «enumeration»
pmxReactorPropEnum pmxReactorTypeEnum pmxPropertySolverPropEnum
+pmxReactorDeltaP +pmxCSTReactor +pmxPropertySolverError
+pmxReactorDuty +pmxPFReactor +pmxPropertySolverValue
+pmxReactorConversion +pmxConversionReactor +pmxPropertySolverLowerBound
+pmxReactorPFRSolutionMethod +pmxEquilibriumReactor +pmxPropertySolverUpperBound
+pmxReactorMaxPhases +pmxGibbsMinReactor +pmxPropertySolverBoundStep
+pmxReactorYield +pmxNonEquilibriumCSTReactor +pmxPropertySolverMinimizer
+pmxReactorIVMethod +pmxPropertySolverInternalAlgorithm
+pmxReactorBypassFraction +pmxPropertySolverIterations
+pmxReactorMaxAvailableConstraints «enumeration» +pmxPropertySolverMaxIterations
+pmxReactorIncrements pmxRateDenomPropertyEnum +pmxPropertySolverWeighting
+pmxReactorGibbsSet +pmxPropertySolverPriority
+pmxRateDenomEquationUnits
+pmxReactorType +pmxPropertySolverActive
+pmxRateDenomActive
+pmxReactorIncrementType +pmxPropertySolverGroup
+pmxRateDenomExponents
+pmxReactorReactionExtent
+pmxRateDenomK0
+pmxReactorReactionConversion
+pmxRateDenomlnK0
+pmxReactorYieldComponent
+pmxRateDenomEa
+pmxReactorGibbsReactive
+pmxRateDenomEaOverR
+pmxReactorMaxTemperature
«enumeration»
+pmxReactorDeltaT
pmxCalculatorTypeEnum
+pmxReactorFracVapor
+pmxReactorFracLLiquid +pmxCalculatorSolver
+pmxReactorFracHLiquid +pmxCalculatorSpecifier
«enumeration»
+pmxReactorSegments pmxRateConstantPropertyEnum
+pmxReactorDeltaPMethod +pmxRateConstantEquationUnits
+pmxReactorParticleDiameter +pmxRateConstantK0
+pmxReactorNEQMassTransfer +pmxRateConstantlnK0
+pmxRateConstantEa «enumeration»
+pmxRateConstantEaOverR pmxCodeSourceEnum
+pmxRateConstantN +pmxCodeSourceVBA
«enumeration» +pmxCodeSourceScript
pmxReactionComponentPropertyEnum +pmxCodeSourceExcel
+pmxReactionComponentStoich +pmxCodeSourceExternal
+pmxReactionComponentFwdOrder +pmxCodeSourceSimple
+pmxReactionComponentRevOrder +pmxCodeSourceQRecycle
«enumeration»
+pmxReactionComponentKeqOrder pmxReactorConstraintEnum
+pmxRCLinear
+pmxRCFischer1974
«enumeration» +pmxRCNSERC1993
pmxReactorConstraintPropEnum +pmxRCLuinstradHaene
+pmxRCNSERC2002
+pmxReactorConstraintNumParms
+pmxRCQuenchTemperature Plate Frame Rating
+pmxReactorConstraintActive
+pmxRCQuenchInletOffsetTemperature
+pmxReactorConstraintParm1
+pmxReactorConstraintParm2 «enumeration»
pmxHEXPlateFramePlatePropEnum
+pmxHEXRPFPlateLabel
+pmxHEXRPFPlateThickness
«enumeration»
«enumeration» +pmxHEXRPFPlateGaugeThickness
pmxReactionPropertyEnum
pmxReactionTypeEnum +pmxHEXRPFPlateChevronAngle
+pmxReactionActive +pmxHEXRPFPlateSurfaceEnhance
+pmxReactionEquation +_pmxUnknownReaction
+pmxKineticReaction +pmxHEXRPFPlateMatofCon
+pmxReactionEquationsToUse +pmxHEXRPFPlateTotalNumber
+pmxReactionConcentrationType +pmxEquilibriumReaction
+pmxReactionConcentrationUnits +pmxConversionReaction
+pmxReactionAssumeEquilibrium
+pmxReactionPhase «enumeration»
+pmxReactionKineticBase pmxHEXPlateFrameGroupPropEnum
+pmxReactionRateBasis +pmxHEXRPFGroupFlowConfig
+pmxReactionRateUnits +pmxHEXRPFGroupFirstPlateType
+pmxReactionCatalystParticleDensity +pmxHEXRPFGroupSecondPlateType
+pmxReactionKeqFromGibbs +pmxHEXRPFGroupNumChanPerFluid
+pmxReactionApproachTemperature +pmxHEXRPFGroupSupplyPassNumber
+pmxReactionConversionBase +pmxHEXRPFGroupDemandPassNumber
+pmxReactionPriority
+pmxReactionConversionBasedOnInlet
+pmxReactionDenomOrder

Enumerators by Use III


46
47

You might also like