Force Excel to Calculate Dependencies In Order

Overview

If you have ever used custom functions in Excel, depending on the complexity of them, you have probably run into an issue where the accuracy of the results was sporadic. There is a quick solution. Use CTRL ALT SHIFT F9.

The lengthier explanation from Microsoft explains that the calculation of worksheets in Excel can be viewed as a three-stage process:

  • Construction of a dependency tree
  • Construction of a calculation chain
  • Recalculation of cell

With the introduction of complex VBA functions, the default calculation can produce inaccurate results because it doesn’t evaluate the dependency tree and calculation chain correctly.

So, if you have this issue, the most complete and thorough (and time consuming) calculation can be initiated by clicking CTRL ALT SHIFT F9. This forces the dependency tree to be rebuilt and recalculates the entire workbook. There are several levels in forcing Excel to calculate.

F9

Recalculates all cells that Excel has marked as dirty, that is, dependents of volatile or changed data, and cells programmatically marked as dirty. If the calculation mode is Automatic Except Tables, this calculates those tables that require updating and also all volatile functions and their dependents.
VBA: Application.Calculate

SHIFT F9

Recalculates the cells marked for calculation in the active worksheet only.
VBA: ActiveSheet.Calculate

CTRL ALT F9

Recalculates all cells in all open workbooks. If the calculation mode is Automatic Except Tables, it forces the tables to be recalculated.
VBA: Application.CalculateFull

CTRL ALT SHIFT F9

Causes Excel to rebuild the dependency tree and the calculation chain for a given workbook and forces a recalculation of all cells that contain formulas.
VBA: Workbooks(reference).ForceFullCalculation (introduced in Excel 2007)

References




How To Maximize Excel by Using Custom Function

Whether you play a technical role or are a financial analyst, Excel is likely a major asset in your toolbox. Whether it is the SUM function, the VLOOKUP function, or one of the many others, we have all used Excel functions for a plethora of reasons. 

There is a lot of potential hidden in Excel that you may not be aware of.  Excel offers the ability to create your own user defined functions, and it’s not hard to create them.  With a little ingenuity and strategic thinking, custom Excel functions can be a huge asset.  

Below are two examples.  Neither is difficult, but they will provide you with a taste of what you can do with custom functions.  The first example calculates a better/worse value based on three inputs (prior period, current period, and expense vs. revenue).  The second concatenates columns together with a user specified delimiter and the option to use quotes around the values.

Background on Custom Functions

Custom functions are Visual Basic for Applications (VBA) code snippets that are stored in modules in a workbook.  This is the same place macros are stored, so it may be familiar.  To open the VBA window, use ALT F11.  Once the window opens, right-click the workbook you want to add the function to in the VBAProject window and select Insert->Module.  A new window will open named Module1.  Custom functions have to be in a module to be accessed in a workbook.

Each function has a function name, input arguments that pass data to the function, and return a value.

A very simple example shows these pieces.  “Test” is the function name.  “Input” is one argument passed to the function.  The function returns a numeric value, which is the input value multiplied by ten.

Function Test(input as double) as Double
    Test=input * 10
End Function 

To use this function, return to your worksheet and enter “=Test(5)” in a cell.  This function can also be found in the Insert Function option by selecting User Defined in the Select A Category dropdown box.  The input parameter doesn’t have to be a value.  A cell reference can be used, just like any other Excel function.  The result should return 50.

Example:  Better(Worse) Calculation

For you finance folks, you will almost always have a better/worse calculation in a spreadsheet that compares two periods.  For revenue, the current period is subtracted from the prior period.  For expense, it is the inverse. 

To accomplish this, we will have a function with 4 parameters. 

  1. Prior Period
  2. Current Period
  3. Whether the numbers being evaluated should be calculated as an expense or revenue
  4. Whether the result returned is in the form of a dollar value or percentage change
Function BetterWorse(Prior_Period As Double, Current_Period As Double, Expense As Boolean, Return_Dollar As Boolean) As Double
    If Expense = True Then 'Calculate as an expense
        If Return_Dollar = True Then 'Return a dollar value
            BetterWorse = Prior_Period - Current_Period
        Else 'Return a percentage
            BetterWorse = (Prior_Period - Current_Period) / Prior_Period
      End If
    Else 'Calculate as a revenue
        If Return_Dollar = True Then 'Return a percentage
            BetterWorse = Current_Period - Prior_Period
        Else 'Return a percentage
            BetterWorse = (Current_Period - Prior_Period) / Current_Period
      End If
    End If
End Function

Below is an example of this function being used.  The result of the custom function resides in column D and E.  Revenue is lower in the current year, resulting in a negative variance.  Expenses are also lower, but result in a positive variance.

The formulas that exist in columns D and E are as follows.

Example:  Concatenation

The need to create a delimited file from Excel is very common.  The problem with doing this is that the entire worksheet is extracted.  If the worksheet had data in rows or columns that are now blank, Excel still exports those blank cells.  One way to overcome this is to create a function that concatenates a range into one cell.  Then, the concatenated values can be copied and pasted to a text file.  Many times this is very handy.  This can obviously be done with a cell formula, but gets time consuming to create when many cells are required.  It is further complicated when quotes around the fields are necessary. 

Function ConcatForExport(InRange As Range, Delimiter As String, UseQuotes As Boolean) As String
    Dim TheCount As Integer
    TheCount = 0
    For Each cell In InRange
        If TheCount = 0 Then
           If UseQuotes = True Then
              strString = Chr(34) & cell.Value & Chr(34)
           Else
              strString = cell.Value
           End If
        Else
           If UseQuotes = True Then
               strString = strString & Delimiter & Chr(34) & cell.Value & Chr(34)
           Else
               strString = strString & Delimiter & cell.Value
           End If
        End If
        TheCount = TheCount 1
    Next cell
    ConcatForExport = strString
End Function

To expand on the variance example above, an additional column has been added to show the use of this function.  Each row passes different parameters.  Columns B through E are concatenated together into one cell.  The delimiter is altered in row 5, and no quotes are around the value in row 4.

The corresponding formulas are below.

 

There are a wealth of opportunities that open up using custom functions.  Adding functionality and automating tasks like the examples above are just the start of what can be done. 




Create Excel Groupings (Outline Levels) to show Essbase Hierarchies

Working with people new to Essbase every three to six months, I am always looking for ways to show users their hierarchies effectively. Many of them don’t have access to Essbase administration services or EPMA.  So, I always fall back to excel as a distribution method, as well as documentation, to show hierarchies.

Expanding hierarchies to all descendants is a great way to show small hierarchies, but, I am always asked to make it a collapsible hierarchy using the Excel grouping feature. The challenge of doing this manually to a hierarchy with thousands of members is that it is extremely time consuming and very error prone.

The following script can be added to any workbook to automate this effort.

Sub CreateOutline()
    Dim cell As Range
    Dim iCount As Integer
    For Each cell In Selection
        'Check the number of spaces in front of the member name 
        'and divide by 5 (one level)
        iCount = (Len(cell.Value) - Len(Trim(cell.Value))) / 5
        'Only execute if the row is indented
        If iCount <> 0 Then cell.EntireRow.OutlineLevel = iCount
    Next cell
    MsgBox "Completed"
End Sub

Setup

First, this sub routine has to be added to a workbook.  Open up the visual basic editor. Right click on the workbook in the project explorer window and add a new module. Paste the code above in the new module.  The editor is in different places in different version.  In Excel 2007 and 2010, the Developer ribbon is not visible by default.  To make it visible, go to the navigator wheel and click Excel Options.  There is a checkbox named Show Developer Ribbon that will make this developer ribbon viewable.

How To Use

First, open the member selection option in the Essbase add-in or smart view and select the parent.  Add all its descendants.  Alternately, change the drill type to all descendants and zoom in on the member of the hierarchy.

Retrieve, or refresh, the data, and make sure the indent is set so the children are indented.  Now, highlight the range of cells that has the hierarchy/dimension that the grouping should be applied. This should include cells in one column of the worksheet.  Open the code editor and place the cursor inside the sub routine you added from above and click the green play triangle in the toolbar to execute the script.  When this is finished, go back to the worksheet with the hierarchy and it will have the hierarchy grouped.

Excel limits the level of groupings to eight. If the hierarchy has more than eight levels, they will be ignored. Now, the hierarchy can be expanded and collapsed for viewing.

Shortcut keys or toolbar buttons can be assigned to execute this function if it is used frequently. If you are interested in doing this, there are a plethora of how-to articles on this topic.  This Google search will get you started if you choose to go down that path.

So, the next time you need to explain a hierarchy in Essbase, or distribute it in a common format, hopefully this script will help.




Creating Hierarchies & Groupings In Excel – One Click Solution

A lot of users like to see hierarchies in Excel and build groupings around these hierarchies so they can be collapsed and expanded easily.  It is not a huge deal to do this for things that don’t change a lot, like months rolling to a quarter, but it can be extremely cumbersome to maintain for organizational or account hierarchies that are large or change frequently.

By adding some VBA code (a macro) to your workbook, managing groupings can be completely automated.  This can be customized for a plethora of different scenarios.  Below are 2 examples that Hyperion users will encounter.  One caveat to this is that Excel limits the number of grouping levels to 8.  If the worksheet has more than 8 levels, the following logic would not provide the expected result.

Creating a Hierarchy Based On Excel Indents

If a spreadsheet exists where the hierarchy is created with the indent (not multiple columns) feature of Excel, select the range for the groupings to be applied.  Execute the following script.  Basically, this loops through the cells you have selected and will create the groupings based on the number of indents in the cell.

Sub CreateGroupingsOnIndents()

Dim cell As Range
For Each cell In Selection
    If cell.IndentLevel <> 0 Then
        cell.EntireRow.OutlineLevel = cell.IndentLevel
    Else
        cell.EntireRow.ClearOutline
    End If
Next

End Sub

Creating a Hierarchy Based On SmartView/Excel Add-In Indents

When retrieving from Essbase, cells are indented by adding 5 spaces to the member name.  By getting the length of the cell, subtracting the number of spaces preceding the member name, and dividing the result by 5, the level of the indent is identified.  Select the cells with the member names and execute the following.

Sub CreateGroupingsOnSpaces()

Dim cell As Range
Dim iLength1 As Integer
Dim iLength2 As Integer
Dim iIndent As Integer

For Each cell In Selection
    iLength1 = Len(cell.Value)
    iLength2 = Len(LTrim(cell.Value))
    iIndent = (iLength1 - iLength2) / 5
    If iIndent <> 0 Then
        cell.EntireRow.OutlineLevel = iIndent
    Else
        cell.EntireRow.ClearOutline
    End If
Next

End Sub

Setup a Module

If you are unfamiliar with adding custom code to an Excel workbook, follow the steps below.

Excel 2000 and below

  1. Select Tools/Macro/Visual Basic Editor
  2. Right click on the workbook in the Project window, and select Insert/Module
  3. Expand the module folder and open the new module (likely module1)
  4. Paste the example above in this window to the right
  5. Execute it by clicking F5 or the green play triangle in the toolbar

Excel 2003 and greater

  1. Select the Navigation Wheel, and check the “Show Developer tab in the Ribbon” checkbox in the Popular tab
  2. Select the Developer Ribbon and click Visual Basic
  3. Right click on the workbook in the Project window, and select Insert/Module
  4. Expand the module folder and open the new module (likely module1)
  5. Paste the example above in this window to the right
  6. Execute it by clicking F5 or the green play triangle in the toolbar

These can also be associated to a custom menu or toolbar if you choose to take the extra step!




Altering Large Numbers Of Cells In Excel A Hundred Times Quicker

Many processes need to write large volumes of data in Excel.  The typical method is to loop through each cell and perform the action.

   Dim CellsDown As Long
   CellsAcross As Long

   Dim CurrRow As Long
   CurrCol As Long
   Dim CurrVal As Long

   '  This can be replaced with the selected range and is just used to illustrate this example.
   CellsDown = 1000
   CellsAcross = 36

   '   Loop through cells and insert values
   CurrVal = 1
   Application.ScreenUpdating = False
   For CurrRow = 1 To CellsDown
       For CurrCol = 1 To CellsAcross
           Range("A1").Offset(CurrRow - 1, CurrCol - 1).Value = CurrVal
           CurrVal = CurrVal   1
       Next CurrCol
   Next CurrRow

Rather than writing the values out cell by cell, it is quicker to store the value in an array and write the array to a range of cells at one time.

   Dim CellsDown As Long
   CellsAcross As Long

   Dim CurrRow As Long
   CurrCol As Long
   Dim CurrVal As Long

   Dim TempArray() As Double

   '  This can be replaced with the selected range and is just used to illustrate this example.
   CellsDown = 1000
   CellsAcross = 36

   '   Update the array
   ReDim TempArray(1 To CellsDown, 1 To CellsAcross)
   Set TheRange = Range(Cells(1, 1), Cells(CellsDown, CellsAcross))

   '   Fill the temporary array
   CurrVal = 0
   Application.ScreenUpdating = False
   For i = 1 To CellsDown
       For j = 1 To CellsAcross
           TempArray(i, j) = CurrVal
           CurrVal = CurrVal   1
       Next j
   Next i

   '   Transfer temporary array to worksheet
   TheRange.Value = TempArray

This same method can be used when altering data.  By changing the following line

            TempArray(i, j) = CurrVal

To this

            TempArray(i, j) = TheRange(i, j) * 3

By using TheRange(i, j), the existing value can be altered

 

The process of writing values cell by cell took 3.16 seconds.  Using the array method, it took .08 seconds, nearly 40 times faster




Altering Large Numbers Of Cells In Excel A hundred Times Quicker

Many processes need to write large volumes of data in Excel.  The typical method is to loop through each cell and perform the action.

   Dim CellsDown As Long
   CellsAcross As Long

   Dim CurrRow As Long
   CurrCol As Long
   Dim CurrVal As Long

   '  This can be replaced with the selected range and is just used to illustrate this example.
   CellsDown = 1000
   CellsAcross = 36

   '   Loop through cells and insert values
   CurrVal = 1
   Application.ScreenUpdating = False
   For CurrRow = 1 To CellsDown
       For CurrCol = 1 To CellsAcross
           Range("A1").Offset(CurrRow - 1, CurrCol - 1).Value = CurrVal
           CurrVal = CurrVal   1
       Next CurrCol
   Next CurrRow

Rather than writing the values out cell by cell, it is quicker to store the value in an array and write the array to a range of cells at one time.

   Dim CellsDown As Long
   CellsAcross As Long

   Dim CurrRow As Long
   CurrCol As Long
   Dim CurrVal As Long

   Dim TempArray() As Double

   '  This can be replaced with the selected range and is just used to illustrate this example.
   CellsDown = 1000
   CellsAcross = 36

   '   Update the array
   ReDim TempArray(1 To CellsDown, 1 To CellsAcross)
   Set TheRange = Range(Cells(1, 1), Cells(CellsDown, CellsAcross))

   '   Fill the temporary array
   CurrVal = 0
   Application.ScreenUpdating = False
   For i = 1 To CellsDown
       For j = 1 To CellsAcross
           TempArray(i, j) = CurrVal
           CurrVal = CurrVal   1
       Next j
   Next i

   '   Transfer temporary array to worksheet
   TheRange.Value = TempArray

This same method can be used when altering data.  By changing the following line

            TempArray(i, j) = CurrVal

To this

            TempArray(i, j) = TheRange(i, j) * 3

By using TheRange(i, j), the existing value can be altered

 

The process of writing values cell by cell took 3.16 seconds.  Using the array method, it took .08 seconds, nearly 40 times faster




Calculating Custom Functions in Microsoft Excel

Microsoft Excel does a great job of calculating only what is needed.  If automatic calculation is turned on (and is by default), it only calculates formulas that have changed since the last calculations.  If automatic calculation is turned off, F9 will accomplish the same thing.

CTRL F9 goes one step further and calculates formulas that have changed, as well as the formulas dependent on them.

CTRL ALT F9 calculates all formulas in the workbook, regardless of whether they changed since the last calculation.

When custom functions are used, Microsoft Excel doesn’t always know the dependencies because the function can reference cells outside those provided in the function arguments.   When this occurs, using CTRL SHIFT ALT F9 is critical to ensure that all cells are calculated correctly.  This rechecks dependent cells and calculates all formulas regardless of whether they have changed since the last calculation.  This is the only way to ensure that all data is calculated.




Better Business Decisions by Automating Redundant Tasks

I started my career as an accountant and never had any aspirations of doing the same thing all day, every day.  While I struggled through what I considered monotonous job functions, I developed a knack for finding ways to automate my job.  As a result, I didn’t have to do repetitive tasks and I had more time to learn the business. Don’t get me wrong, accountants possess a unique set of skills and talent that I respect trumendously. It is a critical function of any business.  So, kudos to you accountants!

When I get involved with building new applications with Hyperion, or updating existing models, it pains me to see accounting, finance, and the staff who support Hyperion continue to perform repetitive tasks that dominate their time.  It can drive talented people to look for employment elsewhere.  It inflates salaries and jeopardizes credibility with an increase in human error. It also deteriorates the quality of business analysis, introducing a greater risk of poor decisions.  Inflated expenses and poor management decisions can be catastrophic to any business.

Automation in accounting and finance areas is critical to productivity.  Being able to support the constant push from management to become better and faster with less resources is always challenging.  If your Hyperion environment is supported outside of finance, IT areas are under just as much scrutiny.  How much of your time, or staff, is spent generating reports?  How much more time could be spent helping analyze the business and adding value to management decisions?  From an IT prospective, how much of your time is spent supporting the environment and responding to requests where answers could be automatically generated?  If 20% of your reparative tasks were eliminated, how much more effective you would you be?  How much more experience would you gain?  How much more marketable would you be both internally and externally?

Many of the possibilities for automation are never discussed.  Most people don’t even realize how much time they spend performing repetitive tasks that could be automated. Some think it would be impossible to automate and others think it would be too expensive.  The examples below were both accomplished in a matter of weeks.  The investment had a positive return within months.  The non-monitory gain was felt immediately.

Don’t think of why it can’t be done.  Think of a solution without constraints and ask, “How can we get there?”  With the proper guidance and background, massive improvements can be accomplished with minimal effort.

To spark some thought, think about these situations.

Monitoring Essbase jobs and keeping users informed of system status

Are you responsible for managing all the jobs that run on Essbase server(s) and are constantly asked if something has completed, or when something will complete, by your users?  Some organizations have a person dedicated to managing this information flow.

I implemented a solution at a large financial institution to conquer this problem.  The result was a solution that required zero effort to maintain and provided a summary of over 50 processes in one web page.  It gave the status of the process, when it last executed, if there were any errors, and a link to the log and error files if they were required.  Access was granted to all the Essbase administrators.  Another page was available for all users that displayed the status of the application, when it was last loaded, when it was last calculated, and several other useful sources of information.

The days of searching through folders on multiple servers are now long gone for system administrators.  Users are more informed and support tickets diminished substantially.  The estimated time savings was 4-6 hours per day.

This solution was built using existing technologies, limited to Maxl, Windows scripting, ASP.NET, and access to an IIS Server to host the website.  It was 100% maintenance free and built dynamically enough so that new applications could be added and applications could be renamed or deleted.  All this is possible without changing any code or processes.

Distribution of reports

A large international organization distributed over 150 reporting templates to an equal amount of people in the US and abroad.  These templates were distributed daily through the monthly close of business.  The daily adjustment cycle finished updating the reporting Essbase application around 2 AM.  When a finance staff member arrived around 8 AM, the work began.  The template was refreshed and saved for each of the 150 business entities.  Emails were then sent to each of the 150 people with their respective report.  This process took about 6 hours every day it was performed.

Using existing technology, a process was created to traverse through a spreadsheet that had 2 columns, which was maintained by finance.  The first was the business unit, followed by the email the report was to be sent to.  Using the Essbase toolkit and Excel, a process was initiated as soon as the database was updated that opened a spreadsheet that included the template, changed the business unit, refreshed the template, saved it, and emailed to the intended recipient.  This process took less than 1 hour and all the reports were distributed before 4 AM.  Customers received their reports earlier (those in Asia a day early), no human errors were made, and the finance staff now had an additional 6 hours to add value.