• Skip to primary navigation
  • Skip to main content
  • Skip to primary sidebar
  • Lee L. Lowery, Jr., PhD, P.E.
  • Research
  • People
  • Contact

Lee L. Lowery, Jr.

Just another CoE WordPress site

Texas A&M University College of Engineering

Uncategorized

Class 37

Posted on July 28, 2021 by Abigail Stason

Learning Objectives – Class 37

After today’s lecture, and after working the homework problems, the student should be able to

  • Work with very simple Block Oriented Systems Simulation program commands. Recognize the similarity between commonly used simulation programs BOSS, SIMAN, ARENA, SIMEVENTS.

Topics covered in today’s class

See main sheet

Typical references regarding simulation languages utilized in industry

  • http://www.arenasimulation.com/   This is the neatest thing you will ever see. Quite a simulation package. On the left side of the screen, click on “View a simulation sample”, then on the right side of the next screen click on “Animations: Automotive, or Banking, or Health Care, or Logistics.” They have everything except someone robbing the bank.
  • http://www.mathworks.com/access/helpdesk/help/toolbox/simevents/
  • http://www.cadmen.com/sec_page/product_solve/Arena/Models.pdf
  • http://www.informs-sim.org/wsc00papers/248.PDF
  • http://www.wintersim.org/pastprog.htm

What the NSF thinks about engineering simulation

  • May 2006 Report of the National Science Foundation Blue Ribbon Panel on Simulation-Based Engineering Science

Typical references of others utilizing simulation in engineering

  • http://cenotes.tamu.edu//files/ABC-SIM/Articles/ABC_Optimization_Of_Crew_Configurations.pdf

Filed Under: Uncategorized

Typical BOSS example problem

Posted on July 28, 2021 by Abigail Stason

Write a BOSS simulation for the hamburger shop shown below:

Filed Under: Uncategorized

Boss help file

Posted on July 28, 2021 by Abigail Stason

Capitalized words have help lists 12/30/1987

 General categories for the help system:

 PROGRAM    : general program structure

 DEFINITION : definition segment of program

 CONTROL    : program control

 LOGIC      : language block constructs for model building

 SYSTEM     : system functions, constants and variables

 OPERATORS  : system operators

 VARIATES   : distributed random number generators

%DEFINITIONS  segment

  Naming Conventions for all types:

    Simple : Name

    Indexed: Name.Number

  Simulation structures:

    RESOURCE   QUEUE        GATE           CHAIN

    HISTOGRAM  STATISTICS   VARSTATISTICS  DISTRIBUTION (or MAPPING)

    ENTITY     ATTRIBUTES   LABELS

  User variable types (all must be initialized):

    REAL  ARRAY  SEQUENCE  INTERVAL  STRING  TEXTFILE

  Define user functions:

    FUNCTION

  Renaming capability:

    ALIAS

%LOGIC segment has the following blocks (statements):

            simulation block statements

ARRIVE     CREATE     SCHEDULE    DEPART    WAIT

SEIZE      PREEMPT    RELEASE

COPY       COMBINE    GATHER      BUNDLE    UNBUNDLE

LINK       UNLINK     SETGATE     TESTGATE

STARTSTAT  ENDSTAT

SEARCH     REMOVE

INTERRUPT  RESET

            programming statements

FOR        WHILE      REPEAT

IF         DOCASES    GOTO        GOSUB     RETURN

PRINT      PRINTLN    EJECTPAGE   CLEARSCREEN

HALT       ABORT

%SYSTEM

  Constants: PI (=3.14159265), PosInf (= 10 to power 30),

             NegInf (= – PosInf), IntPosInf (=32000)

  Functions:

           sin(x)  cos(x)    tan(x)  arctan(x)        (angles in radians)

           exp(x)  log10(x)  ln(x)   sqrt(x)  sqr(x)  abs(x)

           floor(x)   (largest integer <= argument)

           ceiling(x) (smallest integer >= argument)

           sign(x)    (=1.0 if positive, 0.0 if negative)

           CAPACITY        USED            AVAILABLE    RCURNUMBER

           CUMNUMBER       CUMVALUE        CUMZEROS     MAXNUMBER

           CUMPRODUCTNT    CUMPRODUCTVT    LASTTIME

           BLOCKTOTAL      BLOCKCOUNT

  Variables:

           CLOCKTIME       EVENTCHAIN

  Internal Entity Attributes:

           ENTITYNUMBER  RESUMETIME  PREEMPTLEVEL  STATEMENT

           WATCHCHAR

%OPERATORS

    Arithmetic             : +  –  *  /  ^ (exponentiation)

                             max  min (e.g. x max y)

                             mod (x mod y is remainder of x/y)

    Relational operators   : =  <>  <  <=  >  >=

    Logical operators      : or  not  and  xor

    containment operators  : in  notin

    Conditional expressions: USE

    Iterative constructs   : SUM  PRODUCT  MAX  MIN  ARGMAX  ARGMIN

%USE        : Conditional expression

           : USE Val1 IF Cond ELSE USE Val2

             Use may be chained as in the example

  example  : f(x) =  Use 1 if x in [-5,0] else

           :         Use 2 if x in [1,3] else

           :         Use 3;

%SUM

           : SUM{ expr(var.) : var. IN Domain WITH expr. }

           : var. must be a defined variable

  example  : SUM{ Qused[name.i] : i IN <1, 2, 3> WITH i >= 2 }

%PRODUCT

           : PRODUCT { expr(var.) : var. IN Domain WITH expr. }

           : var. must be a defined variable

  example  : PRODUCT { Qused[name.i] : i in <1, 2, 3> with i >= 2 }

%MAX  MIN   : either binary operator (x MAX y) or the iterative operator

           : Operator { expr(var.) : var. IN Domain WITH expr. }

           : var. must be a defined variable

  example  : MIN { Qused[name.i] : i IN <1, 2, 3> WITH i >= 2 }

%ARGMIN ARGMAX : returns the first variable value satisfying min or max

           : Operator { expr(var.) : var. IN Domain WITH expr. }

           : var. must be a defined variable

  example  : ArgMin { Qused[name.i] : i IN <1, 2, 3> WITH i >= 2 }

%VARIATES   : system random variate generators

            RANDOM    CUNIFORM    NORMAL     LOGNORMAL   TRIANGULAR

            EXPD      ERLANG      GAMMA      BETA        WEIBULL

            POISSON   BINOMIAL    DUNIFORM

%PROGRAM       : three segments statements are required in order

 DEFINITION   : contains variables, functions, resources, etc.

  Begin       : optional syntax statement

   statements : definition segment statements

  End;        : optional syntax statement

 CONTROL      : simulation run time and print controls

   directives : run control directives

   EXITLOGIC  : (optional) logic segment for sophisticated program

              : control (see EXITLOGIC)

 LOGIC        : all program blocks representing the model

  Begin       : optional syntax statement

   statements : logic segment statements

END.          : model always terminates with END.

%CONTROL    : see individual help items for the following

   WATCH       view and animation list

   DIRECTIVES  for allowable run control directive

   EXITLOGIC   logic segment for sophisticated program control

%DIRECTIVES for control segment

StopTime   : simulation run length in clock units

StopCount  : run length in departure counts

ResetTime  : time at which statistics are cleared

ResetCount : departure count at which system statistics are cleared

PrintTime  : system statistics print increment in time units

PrintCount : system statistics print increment in departures

Randomize  : randomizes the starting random number seed(ON,OFF)

Seed       : starting random number seed integer in [1,32767]

BlockListing: statement/block summary information (ON, OFF) default is ON

              (cannot be used from within EXITLOGIC)

StatListing: statistics summary information (ON, OFF), default is ON

VarListing: Global variable summary information (ON, OFF), default is ON

Listing    : Enable/disable model listing (ON, OFF), default is ON

             Can be placed anywhere and used multiple times.

%WATCH      : for control segment

           : None of these directives can be used in EXITLOGIC

WatchList  : list of resource, queue and gate names

           : optional display symbol can be specified

           : example WatchList = { myRes:’M’, myQue:254};

           : individual entity WATCHCODE character over rides WATCHLIST

           : the future events chain name for WatchList is EventChain

WatchStatus: Determines the operating state of the animation system

           : (ON, OFF, SINGLESTEP) default is ON with a WatchList

           : OFF otherwise.  SINGLESTEP mode lets user control  simul.

WatchDelay : Approximate delay (micro seconds) between animation displays

           : default = 300.

%EXITLOGIC

   Provides a special logic segment for multiple runs and special

      processing the results of a run

   This logic is activated after the conclusion of each run

   The structure is the same as LOGIC with the following exceptions:

  begin (optional)

     programming statements

     no simulation statements except: SETGATE and RESET

     CLEAR, CONTINUE

 end; (required)

 To initiate a next run one of CLEAR, RESET or CONTINUE must be provided

   otherwise the system will terminate

%CLEAR  : clear simulation for next run

       : Available only in EXITLOGIC

       : clears all statistical quantities and removes all entities

       : Control directives and user variables retain values from the

       :   close of the previous run – user’s reponsibility to establish

       :   appropriate values

%CONTINUE  : resume simulation

       : Available only in EXITLOGIC

       : next simulation run simply continues the previous run

       : Control directives and user variables retain values from the

       :   close of the previous run – user’s reponsibility to establish

       :   appropriate values

%CLEARSCREEN : clears the screen (does not affect printer or file)

%EJECTPAGE  : program control for inserting a page break

           : if output option is print or file – ejects to new page

           : if the screen output is selected, then a clear screen occurs

%GOSUB      : branch to routine at specified label, return is

           : automatically setup by RETURN statement

example    : GOSUB myLabel;

%RETURN     : return from a GOSUB call, returns to statement following

           : the call statement unless an alternative branch is used

           : more than one return exit can be used in GOSUB routine

example    : IF ok THEN RETURN ELSE RETURN { Destination = errLabel };

%RESOURCE   : resource definition

Capacity   : capacity of resource; (1)

Queue      : optional named queue for resource wait list

example    : shop : RESOURCE = { Capacity = 1, Queue = myQ };

%QUEUE      : entity holding list with statistics computed

           : named queue connected to a resource

Capacity   : maximum number entities in list simultaneously;

Discipline : order entitles placed on list-(FIFO,LIFO, CHOICE)

           : CHOICE(KeyExpression); (FIFO)

Histogram  : flow time histogram name; optional

StatOnOff  : (ON,OFF) queue statistics print code; (On)

example    : ShopQ : QUEUE = { Discipline = CHOICE(PRIORITY)};

%CHAIN      : entity holding list with statistics computed

           : for user controlled linking and unlinking

Capacity   : maximum number entities in list simultaneously;

Discipline : order entitles placed on list-(FIFO,LIFO, CHOICE)

           : CHOICE(KeyExpression); (FIFO)

Histogram  : flow time histogram name; optional

StatOnOff  : (ON,OFF) chain statistics print code; (On)

example    : ShopC : CHAIN = { Discipline = CHOICE(PRIORITY)};

%GATE       : logic switch which queues entities if closed

Status     : initial status is OPEN or CLOSE; (OPEN)

Discipline : queueing discipline of waiting entities, FIFO

           : LIFO or CHOICE(Expression); (FIFO)

Histogram  : flow time histogram name; optional

StatOnOff  : (ON,OFF) gate queue statistics print code; (On)

example    : myGate : GATE = { Status = OPEN, Discipline = LIFO};

%STATISTICS : defines a flowtime statistics collection device

Histogram  : name of histogram for distribution; Optional

example    : sysflow : STATISTICS = { Histogram = hdata };

%VARSTATISTICS : defines a variable value statistics collection device

              : use as regular variable, but value statistics kept

Histogram     : name of histogram for distribution; Optional

Protect       : ON – statitics are not cleared by CLEAR or RESET

              : OFF – (default) is statistics are cleared

example       : x : VARSTATISTICS = { Histogram = hdata };

%HISTOGRAM  : data collection device definition

Cells      : number of cells or categories; Required

MinValue   : lower limit of histogram data; Required

MaxValue   : upper limit of histogram data; Required

Protect       : ON – statitics are not cleared by CLEAR or RESET

              : OFF – (default) is statistics are cleared

example    : hdata : HISTOGRAM = { Cells = 4, MinValue = 0,

           : MaxValue = 16 }; used as hdata = value;

%DISTRIBUTION : mechanism to create empirical functions

             : based upon user provided data pairs

             : same as MAPPING

(type)       : type is CONTINUOUS or DISCRETE interpolation

data list    : list of (x, y) data pairs separated by comas

example      : MyDist : DISTRIBUTION(DISCRETE) =

             :           { (0.1, 1), (0.4, 3), (1.0, 6) };

             : x =  MyDist(RANDOM)

%MAPPING      : Empirical function specification

             : see DISTRIBUTION

%ATTRIBUTES   : declaration of entity attributes of type real and array

             : all created entities are initialized to these values

example    : ATTRIBUTES =

           :  { cost = 0, Priority = 3, seq : ARRAY[<1,2,3>] = (0,0,12) };

%LABELS       : declaration of statement labels

example      : LABELS = { thru, prt, out};

%ENTITY     : declares an entity pointer variable

           : used to reference attributes of an entity other

           : than the active entity

           : see SEARCH, REMOVE, CREATE and SCHEDULE

example    : Aent : ENTITY; used as Aent[EntityNumber] – number

           : of current entity assigned to Aent

%SEQUENCE   : denotes a fixed collection of discrete values

           : < start .. end : mesh, repeats or individual elements>

           : if start > end then negative mesh is required

example    : < 1..4, 6, 7, 16..10:-1>

example    : s : SEQUENCE = <1, 2.3, 5>;

%STRING     : a list of characters enclosed in single quotes

example    : s : STRING = ‘Aa1’;

%INTERVAL   : discrete interval

           : [ Left Expression .. Right Expression: Mesh Expression]

           : default interval mesh is 1.

example    : range: Interval = [1 .. 2*i-1 :delta];

           : continuous interval – used only in boolean expressions

           : such as x IN [1, 3.5]

           : [ Left Expression , Right Expression ]

%REAL       : simple variables can take any (nonreserved) name,

           : are automatically of type real and must be initialized

           : applies to global variables and entity attributes

example    : X = 1.0; Yvalue = 0;

%ARRAY      : declaration for dimensioned variables, limit of 3 dimensions

           : ARRAY[ Dom1, Dom2, Dom3] = Array constant or All(value)

           : Index domain(s) must be sequences

           : initial values; can use in ATTRIBUTES

example    : a : ARRAY[ <1..3> ] = (0,0,0);

           : b : ARRAY[ <1..2>,<5,9,10> ] = ( (1,11,15), (3,-2,14) );

%TEXTFILE : associates disk file for user output

         :  with PRINT and PRINTLN

Name     : MSDOS file name (in single quotes),

         : special file names: PRN = printer, CON = screen

Status   : WRITE

example  : f:TEXTFILE = {Name = ‘Myfile.dta’, Status=write};

usage    : println{f, ‘ClockTime = ‘, CLOCKTIME:8:2};

%FUNCTION : user defined inline functions

         : name( argument list ) = Expression;

         : argument names are TEMPORARY variables and can not be

         : names already in use

         : the argument list can be empty

examples : f(a,b) = b*sin(a);

         : JobType() = Duniform(50,100);

%ALIAS      : synonym equate statement for system words

           : and previously defined user names

example    : ALIAS = { Machine = RESOURCE, Stop = HALT };

%ARRIVE     : schedules entities into system

Time       : interarrival time – expression (expr.); Required

OffSet     : delay time before arrive block becomes active;(0)

Limit      : maximum number of batches; (none)

Quantity   : number of entities in each arrival batch; (1)

example    : ARRIVE { Time = DUNIFORM(2,12), Limit = 5};

%DEPART     : removes entities from system

Quantity   : number substracted from StopCount each depart; (0)

example    : DEPART {}; or DEPART {Quantity = 3};

%WAIT       : causes entities to wait for specified time

Time       : time entity is held in block; Required

example    : WAIT { Time = EXPD(5*RANDOM) };

%SEIZE      : captures units from defined resource if available

Name       : resource name; Required

Units      : number of units requested; (1)

Rexcess    : transfer label if requested units are not available; (none)

Qexcess    : transfer label if 1 unit is not available in queue; (none)

example    : SEIZE { Name = Shop, Units = 2, Rexcess = label};

%RELEASE    : returns held units to resource

Name       : resource name: Required

Units      : number of units returned; (1)

example    : RELEASE { Name = Shop, Units = 1};

%ASSIGNMENT : used for assignment statements

example    : cost = cost + 1; x = CLOCKTIME;

%STARTSTAT  : tags entities with time of passing for statistics

Name       : statistics information name; Required

example    : STARTSTAT { Name = sysflow };

%ENDSTAT    : enters flow time from STARTSTAT into statistics

Name       : statistics information name; Required

example    : ENDSTAT { Name = sysflow };

%GOTO       : unconditional branch to block label

Destination: block label of destination; Required

example    : GOTO Inspect;

%IF         : conditional branch statement

              IF cond THEN TrueStmt ELSE FalseStmt;

              or

              IF cond THEN TrueStmt;

condition  : boolean expression (0 or 1 result);

example    : IF RANDOM <= 0.5 THEN  x = x + 1 ELSE GOTO myLabel;

%PRINT      : prints the argument list without a linefeed;

example    : PRINT {<f>,’ x = ‘,x:8:3,’ Time = ‘,CLOCKTIME:5:0};

           : where f is an optional user file name (TEXTFILE)

%PRINTLN    : prints argument list terminated by linefeed and CR.

example    : PRINTLN {<f>,PRIORITY:3:0,’ is an entity attribute’};

           : where f is an optional user file name (TEXTFILE)

%LINK       : places entity on specified chain list

Name       : chain name for linking, CHAIN must be defined; Req.

Cexcess    : if capacitated chain is full then branch to label

example    : LINK { Name = ShopQ, Cexcess = myLabel };

%UNLINK     : takes entities off of the specified chain list

Name       : chain name; Required

Quantity   : number of entities to unlink; Required

Destination: the location for unlinked entities; (NEXTBLOCK)

Condition  : boolean expression for unlinking entities; Optional

           : referenced attributes of candidate entity are used

example    : UNLINK { Name = ShopQ, Quantity = 1};

%COPY       : creates copies of the entity into a copy group

           : all the entities leave as independent entities

Quantity   : the number of copies to be made; Required

CopiesTo   : destination for copies; Required

example    : COPY { Quantity = 2, CopiesTo = label};

%COMBINE     : a group of entities is replaced by 1 entity

            : only the final entity leaves the block

Quantity    : number of entities to combine into one; Req.

UseAttribute: uses the attribute value to determine groupings

Decrement   : expression that decrements Quantity (1)

example     : COMBINE { Quantity = 4, Decrement = 2+x };

            : COMBINE { Quantity = 2, UseAttribute= group};

%PREEMPT    : interrupts seized resource units with larger preemptlevel

           : units are returned by a RELEASE block

Name       : resource name; Required

Units      : number of units requested; (1)

IfNoPreempt: transfer label if units not available; (none)

PreemptedTo: transfer label of preempted entities; (none)

Qexcess    : transfer label if entity can’t obtain resource and

             there is no room in the capacitated queue

Resume     : (ON,OFF) preempted entity uses time remaining or

           : restarts time when returned resource units; (ON)

example    : PREEMPT { Name = Shop, Units = 2, IfNoPreempt = label};

%SETGATE    : modifies named gate status

Name       : gate name for defined GATE from DEFINITION segment

Status     : (OPEN, CLOSE, or INVERT); Required

example    : SETGATE { Name = myGate , Status = OPEN };

%TESTGATE   : if named gate is closed, entity is queued until

           : a SETGATE causes gate to be opened

Name       : name of gate to be tested by entity; Required

IfClosed   : branch destination if gate is closed; (none)

%BUNDLE      : temporarily forms a surrogate to represent a group

            : of entities

Quantity    : number of entities to form one surrogate; Required

Surrogate   : (FIRST or LAST ), surrogate attributes; (LAST)

            : multiple levels of tempory groupings allowed

UseAttribute: uses the attribute value to determine groupings

Decrement   : expression that decrements Quantity (1)

example     : BUNDLE { Quantity = 3, Surrogate = First};

            : BUNDLE { Quantity = 8, UseAttribute= group, Decrement = 2+x};

%UNBUNDLE   : replaces the surrogate entity by the group it

           : represents, note that surrogate is destroyed

example    :  UNBUNDLE {};

%GATHER      : entites wait for Quantity of entities before leaving

Quantity    : number to collect before all are released; Req.

UseAttribute: uses the attribute value to determine groupings

Decrement   : expression that decrements Quantity (1)

example     : GATHER { Quantity = 8, Decrement = 2+x};

            : GATHER { Quantity = 2, UseAttribute= group};

%SEARCH     : scans a resource queue, named queue, chain or gate list

           : for first entity satisfying the given condition

           : returns entity pointer or rank

Name       : name of list to be searched; Required

Condition  : boolean expression compared against list entities

           : referenced attributes of candidate entity are used

Begin      : starting rank of scan; (1)

End        : last possible rank to test; (USED[name])

Rank       : variable name for returning Rank result; (none)

Entity     : entity typed variable name for returned pointer;(none)

           : either Rank or Entity parameter must be specified

           : no entity found then RANK = 0 and ENTITY = NIL

example    : SEARCH { Name = myQue, Entity = Aent, Rank = x

           :          Condition = xvalue – 1 };

%REMOVE     : removes a specified entity from a resource queue, named queue

           : gate, chain or future events list (EVENTCHAIN)

Name       : name of list; Required

Rank       : variable containing rank of entity to be removed;

Entity     : entity variable containing entity pointer;

           : either Rank or Entity parameter must be specified

           : note: system run time error occurs if entity not found

Destination: block label to which the removed entity is transfered

example    : REMOVE { Name = myQue, Entity = Aent, Destination = myLabel };

%WHILE      : WHILE BoolCond DO stmt;

           :    executes Stmt while BoolCond is true

           : Use BEGIN and END for compound statements

example    : WHILE cost < 10 DO cost = cost + 1;

%REPEAT     : REPEAT

                Stmt1; … StmtN;

              UNTIL BoolCond;

            : Stmt1 through StmtN are executed until BoolCond is true;

example     :  x = 0; REPEAT x = x + 1; UNTIL x = 10;

%DOCASES    :

           : DOCASES Expr OF

           :   Case X1: Stmt1; … Case Xn: StmtN;

           :   else – Else statement;  (optional)

             End;

           : where X1 … Xn are numbers, intervals, or sequences

example    : DOCASES i OF

           :    CASE     1: x = x + 1;

           :    CASE <2,3>: x + x + 2;

           :    CASE [4..5]: x = x + 3;

           :    ELSE x = 0;

           : END; “end of DOCASES”

%FOR    :

       : FOR (initial value; BoolExpr; updating expression) DO Stmt;

       : index variable can be global or attribute variable

       : the loop continues while BoolExpr is true

       : updating expression can be any expression

example: FOR (i = 0; i <= 5; i = i+1) DO Println {i:5};

%SCHEDULE   :

           : SCHEDULE{ Entity = ent, Time = expr, Destination = lab};

           : schedules the time of occurrence and point of entry for

           : entities that were created by the CREATE block.  CREATE and

           : SCHEDULE together allow total program control of arrivals

Entity     : refers to an entity variable initialized by a CREATE block

Time       : Time is the absolute activiation time for the entity

Destination: Destination is the statement label where the entity will

           : enter the model at the designated time

example    : SCHEDULE {Entity = Ent, Time = t, Destination = lab};

%CREATE  : program control of entity creation; used with SCHEDULE

        : CREATE { Entity = ent };

Entity  : ENTITY typed variable.  The actual pointer to the

        : created entity is placed into specified entity variable

        : CREATE must be used prior to SCHEDULE to create the entity

        : attributes; initialized values from ATTRIBUTES declaration

example : CREATE { Entity = MyEnt};

%HALT       : causes immediate termination of the simulation run

%ABORT      : causes the simulation system to halt and is most

           : useful within EXITLOGIC and multiple runs

%INTERRUPT  : program is suspended and the interrupt menu is displayed

           : Has same effect as pressing ESC during execution

%RESET      : provides program control for resetting statistics

%RANDOM     : returns zero-one uniform random variate/deviate

example    : myTime = RANDOM;

%DUNIFORM   : discrete uniform r.v.

           : Duniform( LowerLimit, UpperLimit)

             over the discrete interval [LowerLimit .. UpperLimit:1]

example    : myTime = DUNIFORM(1,6);

%CUNIFORM   : continuous uniform random variate

           : Cuniform(LowerLimit, UpperLimit)

           : over the continuous interval [LowerLimit, UpperLimit]

example    : myTime = 3*CUNIFORM(1,6);

%EXPD       : exponentially distributed random variate

           : EXPD(MeanTime)

example    : myTime = 6.0*EXPD(2.34) + 3.14;

%POISSON    : Poisson distributed random deviate

           : Poisson(MeanNumber)

example    : n = Poisson(6.17); (n is a whole number)

%BINOMIAL   : Binomial distributed random variate

           : Binomial(Number, Probability)

           : k = Binomial(10, 0.15); (k is whole number between 0 and 10)

%NORMAL     : Normal random variate

           : Normal(Mean, StdDev)

           : negative values may be returned!

example    : myTime = NORMAL(2.68,1.2) + 4;

example    : myTime = 0 MAX Normal(2.68,1.2);

%TRIANGULAR : Triangular random variate

           : Triangular(LowerLimit, Mode, UpperLimit)

example    : x = Triangular(1,8,15);

%WEIBULL    : Weibull distributed random variate

           : Weibull(Scale, Shape)

%ERLANG     : Erlang distributed random variate

           : Erlang(Mean, Order)

           :  Order = Number of convolutions

%GAMMA      : Gamma distributed random variate with parameters Scale and Shape

           : Gamma(Scale, Shape)

%LOGNORMAL  : LogNormally distributed random variate

           : LogNormal(Mean, Standard deviation)

%BETA       :Beta distributed random variate

           : Beta(Shape1, Shape2)

%NIL        : function which determines if an entity type variable

           : has been found

example    : NIL(xent) – where xent defined in ENTITY definition

%EVENTCHAIN: Predefined name for the system event chain

          : can be used in WatchList, SEARCH, and REMOVE

%CAPACITY  : system function to retrieve or change the capacity

              of a resource, queue or chain

            : CAPACITY[name] – name is resource, chain or named queue

            : CAPACITY[ ResName:QUEUE] to reference default resource Queue

            : only system attribute that can be changed by assignment

%USED  : system function to retrieve current contents of named construct

       : USED[name], to denote a resource queue use name:QUEUE

       : name is resource, queue, chain, gate, varStatistics, statistics

%RCURNUMBER : system function to retrieve number of entities in the resource

           : RCURNUMBER[name] – name is resource

           : units in resource use USED[name]

%AVAILABLE  : system function to retrieve available units of named construct

         : AVAILABLE[name] – name is resource, queue, chain, gate

%MAXNUMBER  : system function to retrieve maximum contents of named construct

     : MAXNUMBER[name] – name is resource, queue, chain, gate

     : to denote a resource queue use name:QUEUE

%LASTTIME  : system function to retrieve last time of named construct undate

     : LASTTIME[name], to denote a resource queue use name:QUEUE

     : name is resource, queue, chain, gate, varStatistics, statistics

%CUMNUMBER  : system function to retrieve cumulative entity entries

     : CUMNUMBER[name],  to denote a resource queue use name:QUEUE

     : name is resource, queue, chain, gate, varStatistics, statistics

%CUMVALUE  : system function to retrieve cumulative value of entries

       : CUMVALUE[name] – name is a varStatistics typed variable

%MAXVALUE  : system function to retrieve maximum value of entries

       : MAXVALUE[name] – name is a varStatistics typed variable

%CUMZEROS  : system function to retrieve number of zero flowtime entries

       : CUMZEROS[name] – name is a Statistics typed variable

%CUMPRODUCTNT : system function to retrieve cumulative number times time

     : statistics data, used in mean duration and mean contents computations

     : CUMPRODUCTNT[name], to denote a resource queue use name:QUEUE

     : name is queue, chain, gate

%CUMPRODUCTVT : system function to retrieve cumulative value times time

     : statistics data, used in mean duration and mean contents computations

     : CumProductVT[name]

     : name is resource, varStatistics, statistics

%BLOCKTOTAL[label] : current value of total entries into block

%BLOCKCURRENT[label] : current number of entities in block

%CLOCKTIME  : system clock time at any point in simulation

%PREEMPTLEVEL : entity read and write attribute used in preempt block

             : to determine if current resource holding entity

             : can be preempted, smaller numbers have higher priority

%RESUMETIME : read only, has remaining wait time if preempted

%ENTITYNUMBER : creation number of the entity

%CURRENTBLOCK : sequential statementnumber for the location of the

               active entity

%NEXTBLOCK  : default label for the next sequential statement

%WATCHCHAR : entity attribute with single character to use in animation

          : activated by assigning character to WATCHCHAR

example   : WATCHCHAR = ‘A’;

Filed Under: Uncategorized

Very Short List of BOSS Commands

Posted on July 28, 2021 by Abigail Stason

  1. PROGRAM
  2. DEFINITION
  3. CONTROL
  4. LOGIC
  5. END.
  1. PROGRAM
    1. “Title of program can be typed here”
  2. DEFINITION – This is where you define everything.
    1. RESOURCES – Things that do the work and can be seized, to the exclusion of others:
      • loader1: RESOURCE = {CAPACITY = 3, QUEUE = line3}; “Generate a resource named loader1, which will do work on entities as they come through the system, and which can be seized by the entities to the exclusion of other entities. This resource has the ability to handle 3 customers at once, and uses a non-standard queue (specified as bigline.) The special queue must have been previously defined above this statement.”loader2: RESOURCE = {CAPACITY = 6}; “Generate a resource which can handle 6 trucks at once, using a standard unnamed default queue having unlimited space.”
      • loader3: RESOURCE = {  }; “Generate a resource with a default capacity = 1, using a standard (unnamed) queue having unlimited room to stand in line”
    2. GATES – Things that open and close, and block the progress of entities:
      • gate1: GATE = {STATUS = CLOSE, DISCIPLINE = FIFO}; “Generate a gate, which can be used to stop the flow of entities if closed. The gate can be born closed, as here, or open, and can release entities FIFO or LIFO.”
    3. LABELS – Code line indicators – gives you the ability to have your customer skip lines of code you don’t want them to read:
      • LABELS = {starthere, checkgate, stuckintraffic, goleft, gostraight, firstline, line1}; “Places (lines of code) to branch to in the program. Labels are actually line labels, such as line1. This could be a line label. A label is a line identifier like a street address. For example if I told you to GOTO 2117 Texas Ave. you would know exactly where to go. If I told you to go to Room 217, you would know exactly where to go. Similarly if you tell an entity to GOTO line1, that’s what he will do – transfer control to the line of code preceded by the label    line1:  Label names MUST be preceded by a letter, i.e. a810 is a legal label name, whereas 810 is not.
    4. LOCAL AND GLOBAL VARIABLES – Local variables (ATTRIBUTES) are personalized variables, accessible only to an individual entity. Global variables are community property, and are accessible to all entities.
      • ATTRIBUTES = {wantstoturnleft = 0, size = 1, color = 5}; “wantstoturnleft, size and color are attributes (local variable names) made up by the programmer. An attribute is a “personal” variable, and every entity born has his own personal value. In this case, as entities are born they will all be born with the following (for example) personal attributes: they don’t want to turn left (wantstoturnleft=0), they are the size of a car (size=1), and they are blue (color=5). If you ran an entity past the statement: size = 2, then that entity, and that entity only would have its size changed to the size of a truck (size = 2.) All other entities would remain unchanged.”
      • moneymade = 400;  “A global variable name made up by the programmer, and initialized as 400. A global variable is one that can be viewed and changed by any entity running around in the system. Thus if an entity later came by and was told moneymade = moneymade + 40, he would change moneymade to 440. Then if a second entity came by and was told the same thing, moneymade would be changed to 480.”
      • payperload = 36.1;  “Another  global variable name”
  3. CONTROL – How to tell the computer program how long to run, etc.
    1. STOPTIME = 240; “How many units of time you wish to run the simulation. Here, the simulation will run 240 nanoseconds, or 240 days, or whatever. This is where, in effect, you set the units of time for the model. Every other time in the model must agree with the units used here.”
  4. LOGIC – How you tell the computer what to do:
    1. THE ARRIVE STATEMENT – Bringing entities into the system to work for you:
      • ARRIVE{TIME = CUNIFORM(0.5,6.5)}; “Borns multiple entities (people, policemen, cars, trucks, computers, etc.) wherein their interarrival times form a continuous uniform distribution between 0.5 and 6.5 seconds, or minutes, or eons. Additional entities continue to be born using this distribution as long as the simulation runs.”
      • ARRIVE{TIME = EXPD(2)}; “Borns repetitive entities having an exponential distribution with a mean of 2 days. Additional entities continue to be born as long as the simulation runs.”
      • ARRIVE{TIME = 0, LIMIT = 6};   “Note you MUST put a LIMIT here!!! Borns 6 entities at the beginning of the simulation, at time = 0 minutes, then quits borning entities.”
      • ARRIVE{TIME = 8}; “Borns repetitive entities, one every 8.00000 days, exactly.”
      • ARRIVE{TIME = 0 MAX NORMAL(20,6)}; “Borns repetitive entities with a normal distribution having a mean of 20 seconds and a sigma of 6 seconds, for as long as the simulation continues.”
      • ARRIVE{TIME = 0 MAX NORMAL(20,6), LIMIT = 32}; “Borns repetitive entities with a normal distribution having a mean of 20 seconds and a sigma of 6 seconds, for as long as the simulation continues or until a maximum of 32 entities have been generated, whichever comes first. The  0  MAX  is used to insure that a negative interarrival time is not generated.”
      • ARRIVE{TIME = NORMAL(500,3)}; “Probably ok, since 500-3*3 is pretty far from negative.”
      • ARRIVE{TIME = NORMAL(5,2)}:  “Note: VERY DANGEROUS! Will probably crash the system.”
    2. SEIZING RESOURCES TO THE EXCLUSION OF OTHER ENTITIES:
      • SEIZE{NAME = loader1}; “This tells the entity who read the statement to seize one unit of capacity from the resource loader1, if possible. If not possible because all of loader1’s capacity is in use, stand in the default queue associated with loader1 until able to do so.”
      • SEIZE{NAME = loader2, UNITS = 2}; “Seize 2 UNITS from loader2 if available, and stand in the default queue associated with loader2 until able to do so.”
      • SEIZE{NAME = loader3, UNITS = 2, REXCESS = ifresourceisbusy, QEXCESS = ifqueueisfull };  “Seize 2 UNITS from loader3 if possible. If the resource is busy, or if you cannot get the 2 requested units then go to the line of code labeled ifresourceisbusy:, and if the queue is full go to ifqueueisfull:. Note that to use QEXCESS, the queue associated with loader2 MUST be a special “named” queue, since un-named queues have, by default, infinite capacity, and hence cannot get full, and will thus never appear to get full. The REXCESS can be used to send entities to special lines of code where they can be given special consideration if they are unwilling to wait in line. For example they can be DEPARTed, they can be sent to do something else while the line gets shorter and then come back later, etc.”
    3. RELEASE – Releasing the resource so others can use it after you are through with it:
      • RELEASE{NAME = loader1}; “After having seized the resource named loader1, release it so other entities can use it.”
      • RELEASE{NAME = loader2, UNITS = 2}; “After having seized two units from the resource named loader2, release them so other entities can use them. Note that if you have someone SEIZE a resource, they must release it before DEPARTing.”
    4. WAIT – Waiting while something gets done:
      • WAIT{TIME = 1}; “Tell the entity which reads this line to wait 1 year (month, nanosecond, etc.)before proceeding to the next line.”
      • WAIT{TIME = CUNIFORM(9,11)}; “Tell the entity to wait a continuous random time, between 9 and 11 seconds. The result will be for her to wait 9.11, 10.47, 10.99 nanoseconds, etc.”
      • WAIT{TIME = DUNIFORM(9,11)}; “Tell the entity to wait a discrete random time, between 9 and 11. The result will be 9, 10, 10, 11, 9, 11, etc.”
      • WAIT{TIME = 0 MAX NORMAL(10,2)}; “Wait for a random time, normally distributed, with a mean of 10, and a sigma of 2.”
      • WAIT{TIME =  EXPD(3)}; “Wait for a random time, exponentially distributed, with a mean of 3.”
      • WAIT{TIME = 3 + EXPD(2) + repairtime}; “Wait for some appropriate time.”
    5. CLOCKTIME – Seeing what time it is during the simulation:
      • time1 = CLOCKTIME; “Look up at the master clock on the wall and see what time it is now, and store it under the variable named   time1.”
      • time2 = CLOCKTIME; “Look up at the master clock and see what time it is now.”
    6. GENERAL CALCULATIONS:
      • timeittook = time2 – time1; “Compute how long it took to do the preceding lines.”
      • cost = cost + 300*(time2-time1);  Cost is a variable, either local (an attribute) or global. If you initialized it in the DEFINITION block using cost = 0, it is global. If you initialized it in the DEFINITION block using an ATTRIBUTES = {cost}; then it is local, and there is one personal “cost” for every entity.
      • value = EXP(LN(LOG10(SQR(SQRT(ABS(FLOOR(junk))))))); “Takes the exp of the natural log of the log base 10 of the squared of the square root of the absolute value of the floor of junk and puts it in value.”
    7. FLOW CONTROL – Testing and directing entities to locations depending on what is happening in the model:
      • IF statementistrue THEN GOTO trueline ELSE GOTO falseline  (This branches to trueline if statementistrue is true, and branches to falseline if statementistrue is false.)
      • IF statementistrue THEN GOTO trueline (This branches to trueline if statementistrue is true, and if statementistrue is false, drops down to the next statement immediately below this one.
      • IF USED[counter1:QUEUE] <= USED[counter2:QUEUE] THEN GOTO getcounter1 ELSE GOTO getcounter2; “This statement tests the number of people in counter1’s default queue, to see if it is currently smaller than the number of people in counter2’s default queue. If so, the entity is directed to go to the line of code labeled getcounter1, and if not he is sent to getcounter2. Note that here the queues are default, standard, unnamed queues.”
      • IF((junk1 > junk2) AND ((a<b) OR (a>junk2))) THEN a = b ELSE a = 2*b; “Logical assignment. Note use of parentheses WHICH ARE REQUIRED!”
      • IF((junk1 > junk2) AND ((a=b) OR (a>junk2))) THEN GOTO label1; “Logical branch.”
      • IF cars > 2 THEN SETGATE{NAME=cargate, STATUS=CLOSED} ELSE GOTO gate1;
      • IF junk1 <  junk2 THEN GOTO cat;
      • IF turnleft = 1 THEN GOTO leftturn ELSE GOTO straight; “If logical branch.”
      • GOTO leftturnlabel; “Direct the entity to go to the line of code labeled  leftturnlabel .”
    8. LABELS – Using labels on lines of code, to identify where you want your customer to go for the next command.:
      • leftturnlabel: a = a+b; “A line of code labeled leftturnlabel, where an entity can be sent.”
      • straightlabel: a = a-b;
    9. DEPART – Removing the entity from the system after you are finished with it:
      • DEPART{ }; “Departs the entity, releasing its memory back to the memory pool.”
    10. GATES – Things such as red lights that can be opened and closed. Used to impede (appropriately) the progress of entities:
      • SETGATE{NAME = gate1, STATUS = OPEN/CLOSE/INVERT}; “Opens and closes a gate named gate1.”
      • TESTGATE{NAME = dog}; “Tests to see if the gate named dog is open. If so, proceed to the next line of code. If not, stay behind the gate, continuously checking its status, and do not proceed until someone, somewhere, opens it.”
      • TESTGATE{NAME = gate1, IFCLOSED = gohere}; “Tests to see if gate1 is open. If so, proceed to the next line of code. If not, send the entity to the line of code labeled gohere. IFCLOSED can be used to send the entity to a  gohere: WAIT=1; timedelay = timedelay+1; GOTO backwhereicamefrom   loop to count how many minutes the entity had to wait for the gate to open.

    END. “Note the period at the end of the END statement. It is required.”

Typical Output:

                         MOR/DS 1.00

Date:  4/13/99                                   Time: 18:39:11

E:\JUNK1\bestmac1.txt

MODEL DESCRIPTION

****************************************************

PROGRAM

“McDondalds with two counters – simple, default que”

“d:\homework\422\bestmac1.bos”

“Last run 4/11/99 – uses valid queue statements”

 

DEFINITION

counter1:RESOURCE = {};

counter2:RESOURCE = {};

LABELS = {getcounter1,getcounter2};

 

CONTROL

STOPTIME=240;

WATCHLIST = {counter1,counter2};

 

LOGIC

[  1]  ARRIVE {TIME=CUNIFORM(0.5,1)};

[  2]  IF USED[counter1:QUEUE] <= USED[counter2:QUEUE] [  3]     THEN GOTO getcounter1

[  4]     ELSE GOTO getcounter2;

[  5]getcounter1:  SEIZE   {NAME    = counter1};

[  6]  WAIT    {TIME     = 30 + EXPD(22)};

[  7]  RELEASE {NAME = counter1};

[  8]  DEPART{ };

[  9] [ 10]getcounter2:  SEIZE{NAME    = counter2};

[ 11]  WAIT {TIME    = 0  MAX  NORMAL(3,2)};

[ 12]  RELEASE {NAME = counter2};

[ 13]  DEPART{ };

[ 14   END.

—————————————————-

 

Simulation Clock   :   240.00

 

Block Information

___Stmt___Line______Label________Name___Total___Current

1      1                 ARRIVE     318         1

2      2                     IF     317         0

3      3                   GOTO     120         0

4      4                   GOTO     197         0

5      5   GETCOUNTER     SEIZE     120       114

6      6                   WAIT       6         1

7      7                RELEASE       5         0

8      8                 DEPART       5         5

9     10   GETCOUNTER     SEIZE     197       113

10     11                   WAIT      84         1

11     12                RELEASE      83         0

12     13                 DEPART      83        83

Filed Under: Uncategorized

Problem 6.11

Posted on July 28, 2021 by Abigail Stason

For the case shown below, and assuming that the plant will cost and produce as expected, determine how much the City of Laredo will have to charge for a gallon of water to amortize the initial investment (operating costs excluded). Assume that the plant will last 20 years, that customers pay their bills monthly, and that the interest rate is 6% per year.

LAREDO CITY COUNCIL APPROVES BUILDING OF PILOT PLANT THAT WILL USE HOLTZAPPLE’S DESALINATION METHOD

Providing enough fresh water for residents is an issue for Laredo, Texas, a city of 200,000 on the Texas-Mexico border. Laredo is almost at the limit of water it can draw from the Rio Grande River, and groundwater in the area is brackish, or salty.

Dr. Mark Holtzapple

Dr. Mark Holtzapple

As a result, the Laredo city council has agreed to spend $1.6 million to build a pilot plant that will field test a new method of desalinating brackish water developed by a Texas A&M University researcher and commercialized by Terrabon L.L.C.

“This is one step in securing and providing water in the future for not only Laredo, but the entire state, with the development of this pilot project,” said Laredo city council member Gene Belmares.

The desalination plant, which will produce 50,000 gallons of water a day, will test water desalination technology developed by Mark Holtzapple, a professor in Texas A&M’s Artie McFerrin Department of Chemical Engineering.

“We desalinate using vapor compression, a method first employed on ships in World War II,” Holtzapple said. “We have updated this old approach using advanced technology such as high-capacity, non-fouling heat exchanger and a low-cost, high-efficiency StarRotor compressor.

“In addition we operated at higher pressures than is traditionally employed. Compared to traditional technology, these innovations lower both the capital cost and operating cost.”

The Texas Engineering Experiment Station (TEES) and The Center for Applied Technology (TCAT), a center within TEES, will act as the technology integrator and analyst for the project.

Additionally, Terrabon, L.L.C., of Houston, an energy and water treatment technology company, will design and construct the advanced vapor demonstration plant. The American Water’s Applied Water Management Inc., acting as a subcontractor for Terrabon will operate and monitor the demonstration plant.

The project will demonstrate the commercial viability of AdVeTM, a new technology that could reduce the capital and operating costs of water purification and provide a low-cost solution to Texas’ water problems. AdVeTM (advanced vapor-compression evaporation) uses low-cost, high-efficiency StarRotor compressors developed, by Holtzapple’s team and non-fouling heat exchangers to desalinate brackish and salty water at a cost that is significantly less expensive than desalination by reverse osmosis.

The Artie McFerrin Department of Chemical Engineering is part of the Dwight Look College of Engineering on the Texas A&M University campus in College Station, Texas.

The Texas Engineering Experiment Station is the engineering research agency of the State of Texas and a member of The Texas A&M University System.

Terrabon, L.L.C. was formed in 1995 to commercialize three technologies that share the same suite of patented intellectual property developed at Texas A&M University.Â

Written by: Tim Schnettler

Additional coverage:

San Antonio Business Journal

Filed Under: Uncategorized

Class 32

Posted on July 28, 2021 by Abigail Stason

Learning Objectives – Class 32

After today’s lecture, and after working the homework problems, the student should be able to

  • Perform a hand simulation solution for a simple engineering system

Topics covered in today’s class

Why you must often run each case multiple times: Consider the results of a single simulation for the trucks in the previous problem –  $480 profit/day. Boss says “Great job” and expecting great profits, goes and buys a Porsche. The job starts and the first day the job makes $230/day. Boss says “Bad employee”, fires you, and sells the Porsche at a 50% loss.

Now consider what you would get had you made multiple runs:  $480/day, $230/day, $420/day, $350/day, $380/day, $220/day, $260/day, $310/day, $490/day, …

See the problem? The $480/day was indeed a valid answer, but it was not the mean. Also, had you simulated the problem multiple times, the $230/day would have also shown up and you could have warned the boss of its occasional appearance. Running the simulation multiple times allows you to not only give the boss the daily mean, it also lets you predict the probable high and low daily values.

For an example of output, click here.

Filed Under: Uncategorized

Solution to problem

Posted on July 28, 2021 by Abigail Stason

For the dirt hauling system shown below, perform a hand simulation.

Clock Time at Start of Operation Entity Under Discus-sion Where is the Entity? What Operation Is Being Performed? Random Number Used for Simulation Probable Time Required for Operation Time Operation can Begin Time at End of Operation
 0.00 ST Hill Loading 0.74 12.07 0.00 12.07
0.00 LT Hill Queue – – 0.00 12.07
12.07 LT Hill Loading 0.13 9.123 12.07 21.195
12.07 ST Road Travel to Pit 0.89 34.089 12.07 46.161
21.195 LT Road Travel to Pit 0.04 24.164 21.195 45.359
45.359 LT  Pit Unloading 0.94 14.067 45.359 59.426
46.161 ST Pit Queue – – 46.161 59.426
59.426 ST Pit Unloading 0.42 2.724 59.426 62.150
 59.426 LT Road Travel to Hill 0.34 4.360 59.426 63.786
62.150 ST Road Travel to Hill 0.47 4.880 62.150 67.030

Filed Under: Uncategorized

Hauling dirt simulation by hand

Posted on July 28, 2021 by Abigail Stason

For the dirt hauling system shown perform a hand simulation.  Large truck size = 27 to 33 cy, small truck size = 19 to 21 cy, both normally distributed.  Time distributions shown are in minutes and are the same for both trucks.

Clock Time Entity Under Discussion Where is the Entity? What Operation Is Being Performed? Random Number Used for Simulation Probable Time Required for Operation Time Operation can Begin Time At End of Operation Random  Number Used for Load Size Load Size Total Dirt Hauled

Filed Under: Uncategorized

Problem 6.1

Posted on July 28, 2021 by Abigail Stason

A trucking firm has the job of hauling dirt from a hill to a pit. The job will take about a year to complete. Times involved in loading, hauling, dumping the dirt and returning are as follows:

 

Small truck information:

Time to load = normal distribution, 5 minutes mean, 2 minutes sigma.

Time to travel to pit = uniform distribution from 20 to 30 minutes

Time to unload = 2 minutes exponential distribution

Time to return to hill from pit = normal distribution, 15 minutes mean, 3 minutes sigma

Capacity = 50 cy

Random numbers to be used: 0.87, 0.41, 0.94, 0.47, 0.67, 0.32, 0.65, 0.62, in that order, as needed.

Large truck information:

Time to load = normal distribution, 10 minutes mean, 3 minutes sigma.

Time to travel to pit = uniform distribution from 30 to 40 minutes

Time to unload = 3 minutes exponential distribution

Time to return to hill from pit = normal distribution, 10 minutes mean, 8 minutes sigma

Capacity = 100 cy

Random numbers to be used: 0.12, 0.16, 0.45, 0.34, 0.31, 0.65, 0.36, 0.12, in that order, as needed.

 

There is only one front end loader available to load the trucks, and only one unloading position is available at the pit. Perform a hand simulation to study the behavior of this engineering system. At the beginning of the day the small truck has arrived before the large truck. Study the system until both trucks have made one trip to the Pit, and have returned to the Hill, utilizing the BOSS Hand Solution Table to organize your solution.

Filed Under: Uncategorized

Simulation hand solution form

Posted on July 28, 2021 by Abigail Stason

Clocktime Entity Sees at Beginning of Operation Entity Under Discussion Location of Entity at Start of Operation What Operation Is Being Performed Location of Entity at End of Operation Random Number Used for Simulation Probable Time Required for Operation Time Operation can Begin Clocktime Entity Sees at End of Operation

 

Filed Under: Uncategorized

  • « Go to Previous Page
  • Go to page 1
  • Interim pages omitted …
  • Go to page 8
  • Go to page 9
  • 10
  • Go to page 11
  • Go to page 12
  • Interim page numbers omitted …
  • Go to page 37
  • Go to Next Page »

Pages

  • Contact
  • Lee L. Lowery, Jr., PhD, P.E.
  • Office Hours

© 2016–2025 Lee L. Lowery, Jr. Log in

Texas A&M Engineering Experiment Station Logo
  • College of Engineering
  • Facebook
  • Twitter
  • State of Texas
  • Open Records
  • Risk, Fraud & Misconduct Hotline
  • Statewide Search
  • Site Links & Policies
  • Accommodations
  • Environmental Health, Safety & Security
  • Employment