PDA

View Full Version : How to updated pivot tables on different tabs from user form parameters?



dovermac
08-04-2014, 04:01 AM
Here is the scenario. I'm a novice at best. This is a macro-enabled workbook for the Board of Education. The workbook is 31MB so not sure where I could post it. If you could see it, you would click on View on the top and then look to the right on the ribbon. Click on the Parameter Selection icon. I'll try to attach this shortly. My work is locked down pretty good.


This allows the user to select the entity to examine. If they do not select an ISD in combobox1, it should default to everything. If they select an ISD like Oakland Schools above, but nothing in Combobox2 than all School Districts will be included and so on. Once they have made their selection, they click OK. Now, what hopefully should happen is the data for their selection should be pulled from the “Combined” tab and put in the Pivot Tables on the Working Pivot Tables tab. Once that is done, another function should take the data from these Pivot tables and “refresh” the graphs and charts on the Summary tab at the front of the workbook.



One thing I’m still trying to correct is the data that populates this workbook comes from a web site that must be downloaded manually (don’t ask). It comes down as csv. You can see from the image above the “code” columns should be 5 characters with leading zeroes. Unfortunately, the source data is not that way. I have saved the source file as xlsm, formatted these code columns as custom since text won’t work and imported them into the workbook. The data moved over to the Pivot Tables (manually done to this point) does not maintain the leading zeroes.

dovermac
08-05-2014, 04:21 PM
BUMP

Can anyone help me please? The workbook is now on dropbox if interested.

Bob Phillips
08-06-2014, 12:30 AM
Dropbox is pretty big, any clues as to where on Dropbox?

dovermac
08-06-2014, 03:06 AM
I'm sorry, here is the link to the workbook. You might have to add the custom tab (CallUserForm).

https://www.dropbox.com/s/dmrhr24naan1g79/MDE_Executive_Dashboard.xlsm

Thank you for looking!

Bob Phillips
08-06-2014, 04:27 AM
Okay, I have the workbook, what next? I can't see a Parameter Selection icon on the VIew tab, I cannot see a combobox, nor any image above the "code".

dovermac
08-06-2014, 04:57 AM
Ok, on the View ribbon, right click where there is nothing and left click on customize the ribbon. Change the drop down from popular commands to macros and you should see CallUserForm and CallUserForm2. You only need the first one. Let me know if you get that far.

Bob Phillips
08-06-2014, 05:18 AM
Okay, I thought it would already be on the ribbon, didn't realise I needed to do that.

The OK button does nothing, so are you asking for some code that will reset the pivot's source data to the data based upon the selections? Can a user request multiple ISDs/Districts/Buildings?

You really should store this data in a database and just use Excel to pull it out and display it.

dovermac
08-06-2014, 05:24 AM
Believe me, I agree with you, but this is how they want it done. I know the ok button does nothing, because I don't have a clue as to how to approach this.

If the user does not select anything in combobox1, than by default everything in the combined tab will be used (or summed up). If a user selects an ISD, but no specific district, than all districts will be used, and so on. Does that make sense?

Bob Phillips
08-06-2014, 05:33 AM
Yeah, I got that, but could they select Oakland Schools and Ottawa ISD (as an example), or will it always be a singleton selection or blank?

dovermac
08-06-2014, 05:42 AM
My understanding is one school or all, if you know what I mean. Not picking scattered names here or there to compile.

Bob Phillips
08-06-2014, 02:18 PM
Okay, here we go. I'll post it in sections, the workbook is far too big.

First, add a new worksheet called scratch, I use this in the code. Uo can hide if you wish.

Second, in PivotTable1 and PivotTable2, deselect the Blanks and School Year from the school years list.

Replace the CallUserForm procedure with the following


Public Sub CallUserForm()
Dim mpForm As ParameterSelection
Dim wsCombined As Worksheet
Dim mpTotalsRow As Long
Dim mpTotal As Double

Set wsCombined = Worksheets("Combined")

Set mpForm = New ParameterSelection
With mpForm

.Show
If Not .Cancel Then

Call FilterPivot("EnrollmentByGrade", .ISDCode, .DistrictCode, .BuildingCode)
Call FilterPivot("TotalEnrollmentTrend", .ISDCode, .DistrictCode, .BuildingCode)
Call FilterPivot("PivotTable1", .ISDCode, .DistrictCode, .BuildingCode) 'Race/Ethicity Makeup Trend
Call FilterPivot("PivotTable2", .ISDCode, .DistrictCode, .BuildingCode) 'Other Demographic Enrollment Trend

Worksheets("Summary").Range("B3").Value = .ISDCode
Worksheets("Summary").Range("B4").Value = .DistrictCode
Worksheets("Summary").Range("B5").Value = .BuildingCode
If .ISDCode = NoSelection Or .DistrictCode = NoSelection Or .BuildingCode = NoSelection Then

Worksheets("Summary").Range("B6:D8").ClearContents
ElseIf .BuildingCode <> NoSelection Then

mpTotalsRow = Worksheets("EEM").Columns(colEEM.BuildingCode).Find(.BuildingCode, After:=Worksheets("EEM").Cells(1, colEEM.BuildingCode)).Row
Worksheets("Summary").Range("B6").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.Address)
Worksheets("Summary").Range("B7").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.City) & " " & _
Worksheets("EEM").Cells(mpTotalsRow, colEEM.State) & " " & _
Worksheets("EEM").Cells(mpTotalsRow, colEEM.Zip)
Worksheets("Summary").Range("B8").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.Phone)
End If

If .BuildingCode <> NoSelection Then

mpTotalsRow = wsCombined.Columns(colCombined.BuildingCode).Find(.BuildingCode, After:=wsCombined.Cells(1, colCombined.BuildingCode)).Row
ElseIf .DistrictCode <> NoSelection Then

mpTotalsRow = wsCombined.Columns(colCombined.DistrictCode).Find(.DistrictCode, After:=wsCombined.Cells(1, colCombined.DistrictCode)).Row
Else

mpTotalsRow = wsCombined.Columns(colCombined.ISDCode).Find(.ISDCode, After:=wsCombined.Cells(1, colCombined.ISDCode)).Row
End If

With wsCombined

mpTotal = .Cells(mpTotalsRow, colCombined.TotalEnrol).Value
Worksheets("Summary").Range("H3").Value = .Cells(mpTotalsRow, colCombined.American).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I3").Value = .Cells(mpTotalsRow, colCombined.American).Value / mpTotal
Else
Worksheets("Summary").Range("I3").Value = 0
End If
Worksheets("Summary").Range("H4").Value = .Cells(mpTotalsRow, colCombined.Asian).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I4").Value = .Cells(mpTotalsRow, colCombined.Asian).Value / mpTotal
Else
Worksheets("Summary").Range("I4").Value = 0
End If
Worksheets("Summary").Range("H5").Value = .Cells(mpTotalsRow, colCombined.African).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I5").Value = .Cells(mpTotalsRow, colCombined.African).Value / mpTotal
Else
Worksheets("Summary").Range("I5").Value = 0
End If
Worksheets("Summary").Range("H6").Value = .Cells(mpTotalsRow, colCombined.Hispanic).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I6").Value = .Cells(mpTotalsRow, colCombined.Hispanic).Value / mpTotal
Else
Worksheets("Summary").Range("I6").Value = 0
End If
Worksheets("Summary").Range("H7").Value = .Cells(mpTotalsRow, colCombined.Hawaiian).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I7").Value = .Cells(mpTotalsRow, colCombined.Hawaiian).Value / mpTotal
Else
Worksheets("Summary").Range("I7").Value = 0
End If
Worksheets("Summary").Range("H8").Value = .Cells(mpTotalsRow, colCombined.White).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I8").Value = .Cells(mpTotalsRow, colCombined.White).Value / mpTotal
Else
Worksheets("Summary").Range("I8").Value = 0
End If
Worksheets("Summary").Range("H9").Value = .Cells(mpTotalsRow, colCombined.TwoOrMore).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I9").Value = .Cells(mpTotalsRow, colCombined.TwoOrMore).Value / mpTotal
Else
Worksheets("Summary").Range("I9").Value = 0
End If
End With
End If
End With
End Sub

Bob Phillips
08-06-2014, 02:19 PM
I also use Enums for column ids, so add this code to a standard code module. Put it at the start of the module, before any code procedures that you might have


Public Const NoSelection = "(All)"

Public Enum colCombined
ISDCode = 2
ISDName
DistrictCode = 4
DistrictName
BuildingCode = 6
BuildingName
TotalEnrol = 9
American = 12
Asian
African
Hispanic
Hawaiian
White
TwoOrMore
End Enum

Public Enum colEEM
BuildingCode = 2
BuildingName
DistrictCode = 4
DistrictName
ISDCode = 6
ISDName
Phone = 13
Address
City
State
Zip
End Enum

Bob Phillips
08-06-2014, 02:20 PM
Replace all of the ParameterSelection form code with the following



Private mcCancel As Boolean
Private mcISDCode As Long
Private mcDistrictCode As Long
Private mcBuildingCode As Long
Private mcBuildingRow As Long

Public Property Get Cancel()
Cancel = mcCancel
End Property

Public Property Get ISDCode()

With Me.ComboBox1

If .ListIndex = -1 Then

ISDCode = NoSelection
Else

ISDCode = mcISDCode
End If
End With
End Property

Public Property Get DistrictCode()

With Me.ComboBox2

If .ListIndex = -1 Then

DistrictCode = NoSelection
Else

DistrictCode = mcDistrictCode
End If
End With
End Property

Public Property Get BuildingCode()

With Me.ComboBox3

If .ListIndex = -1 Then

BuildingCode = NoSelection
Else

BuildingCode = .List(.ListIndex, 1)
End If
End With
End Property

Public Property Get BuildingRow()
With Worksheets("EEM").Columns(colEEM.BuildingCode)

BuildingRow = .Find(mcBuildingCode, After:=.Cells(1, colEEM.BuildingCode)).Row
End With
End Property


Private Sub CancelButton_Click()
mcCancel = True
Me.Hide
End Sub

Private Sub OKButton_Click()
mcCancel = False
Me.Hide
End Sub

Private Sub ComboBox1_Change()

With Me

With .ComboBox1

If .ListIndex <> -1 Then

mcISDCode = .List(.ListIndex, 1)

Set rng = FilterData(colEEM.DistrictName, "=AND(RC[+1]=" & mcISDCode & ",RC[-2]<>R[-1]C[-2])")
End If
End With

.ComboBox2.List = Application.Transpose(Application.Transpose(rng))
End With
End Sub

Private Sub ComboBox2_Change()

With Me

With .ComboBox2

If .ListIndex <> -1 Then

mcDistrictCode = .List(.ListIndex, 1)

Set rng = FilterData(colEEM.BuildingName, "=AND(RC[+1]=" & mcDistrictCode & ",RC[-2]<>R[-1]C[-2])")
End If
End With

.ComboBox3.List = Application.Transpose(Application.Transpose(rng))
End With
End Sub

Private Sub ComboBox3_Change()

With Me

With .ComboBox3

If .ListIndex <> -1 Then

mcBuildingCode = .List(.ListIndex, 1)
End If
End With
End With
End Sub

Private Sub UserForm_Initialize()
Dim rng As Range
Set rng = FilterData(colEEM.ISDName, "=RC[-2]<>R[-1]C[-2]")
ComboBox1.List = Application.Transpose(Application.Transpose(rng))
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
If CloseMode = vbFormControlMenu Then

Cancel = True
Call CancelButton_Click
End If
End Sub

Private Function FilterData( _
KeyColumn As Long, _
SelectBy As String) As Range
Dim ws As Worksheet
Dim LR As Long
Dim rng As Range

Set ws = Worksheets("EEM")
With ws

LR = .Cells(.Rows.Count, 1).End(xlUp).Row

.Columns(KeyColumn + 1).Insert
.Cells(1, KeyColumn + 1).Value = "temp"
.Cells(2, KeyColumn + 1).Resize(LR - 1).FormulaR1C1 = SelectBy

Set rng = .Cells(1, KeyColumn + 1).Resize(LR)
rng.AutoFilter Field:=1, Criteria1:="=TRUE"
On Error Resume Next
Set rng = rng.SpecialCells(xlCellTypeVisible)
On Error GoTo 0
End With

With Worksheets("scratch")

.UsedRange.ClearContents
rng.Offset(0, -1).Copy .Range("A1")
rng.Offset(0, -2).Copy .Range("B1")
LR = .Cells(.Rows.Count, 1).End(xlUp).Row

Set FilterData = .Range("A2").Resize(LR - 1, 2)
End With

ws.Columns(KeyColumn + 1).Delete
End Function

Bob Phillips
08-06-2014, 02:21 PM
And finally, add this to a standard code module


Public Function FilterPivot( _
ByVal PivotTable As String, _
ByVal ISDCode As String, _
ByVal DistrictCode As String, _
ByVal BuildingCode As String) As Boolean
Dim pvtItem As PivotItem

Application.ScreenUpdating = False

With Worksheets("Working Pivot Tables").PivotTables(PivotTable)

.PivotFields("ISDCode").EnableMultiplePageItems = False
.PivotFields("DistrictCode").EnableMultiplePageItems = False
.PivotFields("BuildingCode").EnableMultiplePageItems = False

With .PageRange

.Cells(1, 2).Value = ISDCode
.Cells(2, 2).Value = DistrictCode
.Cells(3, 2).Value = BuildingCode
End With
End With

Application.ScreenUpdating = True
End Function

Bob Phillips
08-06-2014, 02:26 PM
Last thing, on your Summary worksheet, I would remove gridlines and row and column headers for better visuals. On the Enrollment By Grade and Total Enrollment Trend graphs, I would delete the legends, they add nothing. and on the Race/Ethicity Makeup Trend I would move the legend to the bottom, as per the Other Demographic Enrollment Trend graph. And hide the Field Lists for all of these pivot charts.

dovermac
08-06-2014, 02:59 PM
Wow! I'm getting a migraine looking at all this. Ok, first thing, if I replace the calluserform code with yours, will all of your stuff run when I click on the icon in the ribbon? Second, you want me to replace all the parameter selection code with yours? Will this maintain the default selection of everything if nothing is selected or every district if nothing is selected in combobox2? Lastly, I only have 2 modules for the user forms I designed. The first looks like this:


Sub CallUserForm()

ParameterSelection.Show

End Sub

Should I add those 2 sections destined for the standard module and just copy it above the code you have to replace the one line I have for the calluserform?

I can't thank you enough for this really. I am so grateful, you have no idea.

Bob Phillips
08-07-2014, 12:19 AM
I haven't changed anything functionally, just added code to handle those selections. As such, after installing of this code, the form will look the same, and they can enter the same data (BTW, the tab order on the form is wrong, it tabs from ISD->District->OK button->Building, it should be Building->OK button). Most of my code kicks in when you click the OK button, although I have also changed the form initialize and combobox1 and combobox2 click events to load the next combobox more efficiently than your original code - which is what I am using the new scratch worksheet for).

The code that I added caters for no District or no Building, assuming all in those cases (I did some checks, but you will need to test to make sure it is all working okay).

Regarding the modules, you can add my extra code (form code excepted) to either of your existing modules, or create extra modules, it will not affect anything. I tend to group my code, so I would have one module all of the global variables, the enums and so on in thread #12 above), with the two form startup procedures (my replacement CallUserForm code in thread #11 above and your existing CallUserForm2 code), and another for helper procedures (the FilterPivot code in thread #14 above).

One other thing I forgot to mention. On your Working Pivot Tables sheet you have 4 pivots that drive the charts on Summary. Three of them just have ISD, District and Building report filters, but the first one, EnrollmentByGrade, has an extra filter on School Year. I think you should remove that as it might unnecessarily restrict the charts.

dovermac
08-07-2014, 06:07 AM
Ok, I will start putting your code in and see what happens. One other thing I forgot is the way the data is added into the workbook. The superintendent has to d/l it from a website and it's emailed to them as a CSV file. It's lame I know but I can't change it. I've tried to attach a snapshot, but it keeps giving me errors.


You can see the 3 columns with the "ISD Code, District Code, and Building Code" are not formatted correctly (columns B, D, and F). They want them all 5 characters with leading zeros. Now since this is CSV and the data is not entered that way, I tried formatting these as "custom" since text would not work and copying the files into the macro enabled workbook. The problem as you would imagine is when your code or any tried to move these over to the pivot tables, they go back to the original number of characters. Is there a way to correct that or since the source is CSV, is that not possible? This system is ridiculous imo.

This is what the CallUserform2 calls which is my other user form. This is what I have the User click on to grab the CSV file and place it in the combined tab of the macro-enabled workbook. Is there anything I can do here to somehow automate this conversion so it stays "set in stone."?


Option Explicit

Private Sub CancelButton_Click()
Unload Me
End Sub

Private Sub OKButton_Click()
Dim strCSV, shtName As String
Dim csvWkbk, wkbk As Workbook
Dim lastRow As Long

'This sets a link to your macro workbook (that you run this from)
Set wkbk = ActiveWorkbook

'This gets the CSV file name out of the textbox you stored it in from your OpenButton_Click macro
strCSV = TextBox2.Value
shtName = Me.ComboBox1.Value 'This might need to change, I am not sure if you have to reference the user form first

'This opens the CSV workbook
Workbooks.Open strCSV

'This sets a link to the CSV workbook
Set csvWkbk = ActiveWorkbook

'Find the last row of the sheet you want in your wkbk assuming column A is always populated
lastRow = wkbk.Sheets(shtName).Range("A" & Rows.Count).End(xlUp).Row

'This copies the data from the CSV workbook (all cells that are filled in) to the first blank row on the tab in your macro workbook
wkbk.Sheets(shtName).Range(csvWkbk.Sheets(1).UsedRange.Address(0, 0)).Offset(lastRow, 0).Value = csvWkbk.Sheets(1).UsedRange.Value

'This closes the csv workbook
csvWkbk.Close
Unload Me
End Sub

Private Sub TextBox2_Change()

End Sub

Private Sub UserForm_Activate()
With Me.ComboBox1
.Clear
.AddItem "Combined"
.AddItem "Count"
.AddItem "Student Count"
.AddItem "Finance"
.AddItem "Accountability"
.AddItem "EdEval"
.AddItem "Staffing"
.ListIndex = 0
End With
End Sub

Private Sub ComboBox1_Change()
End Sub



Private Sub OpenButton_Click()
Dim FileToOpen As Variant
'added to start in the wanted folder
ChDrive "C:\"
ChDir "C:\Dashboard\"
FileToOpen = Application.GetOpenFilename()
If FileToOpen = False Then Exit Sub
TextBox2.Value = FileToOpen
End Sub

Bob Phillips
08-07-2014, 02:14 PM
Sorry, I am not quite getting this. I can see that all three codes on Combined are formatted as 5 digits, but the codes are not shown in the pivots, apart from the report filters. But as I understand it, the analysis is done on Summary, and here District and Building are 5 digits. Only ISD isn't, and that could be formatted to 5 digits.

dovermac
08-07-2014, 02:32 PM
What I did was took all 5 years, d/l the CSV files, formatted those 3 columns as "custom" and then used my Data Acquisition form (aka CallUserForm2) to upload them in order to the combined tab so they looked correct. My project leader noted that the pivots are not reflecting the combined codes as 5 chars. I think that's the because the data was originally CSV and in many cases only 1 character, not 5. If you want, I could throw one original CSV file so you can see what I'm talking about. I'm just wondering is it possible to go from, for example, a 1 character column under CSV, to a 5 character column that gets "copied" around without losing its formatting? I'm pretty sure my way won't work for an executive.

dovermac
08-07-2014, 02:43 PM
Here is what I am talking about. This superintendent will periodically request a data file and this is exactly how they will get it.

https://www.dropbox.com/s/r0dzbfkr056xx9i/86950ca8-3e5f-40a1-ab1a-f8eb2501c8cc.csv

Is there a way to automate it as it's put into the workbook with 5 char columns for those code columns?

dovermac
08-07-2014, 02:56 PM
An update. I injected all your code. When I select an ISD, District, and School Bldg (doesn't matter which combination), I get a run-time error 1004: ## is not an item of this field. The line below in red is always the culprit.

Public Function FilterPivot( _
ByVal PivotTable As String, _
ByVal ISDCode As String, _
ByVal DistrictCode As String, _
ByVal BuildingCode As String) As Boolean
Dim pvtItem As PivotItem

Application.ScreenUpdating = False

With Worksheets("Working Pivot Tables").PivotTables(PivotTable)

.PivotFields("ISDCode").EnableMultiplePageItems = False
.PivotFields("DistrictCode").EnableMultiplePageItems = False
.PivotFields("BuildingCode").EnableMultiplePageItems = False

With .PageRange

.Cells(1, 2).Value = ISDCode
.Cells(2, 2).Value = DistrictCode
.Cells(3, 2).Value = BuildingCode

Bob Phillips
08-08-2014, 02:36 AM
What I did was took all 5 years, d/l the CSV files, formatted those 3 columns as "custom" and then used my Data Acquisition form (aka CallUserForm2) to upload them in order to the combined tab so they looked correct. My project leader noted that the pivots are not reflecting the combined codes as 5 chars. I think that's the because the data was originally CSV and in many cases only 1 character, not 5. If you want, I could throw one original CSV file so you can see what I'm talking about. I'm just wondering is it possible to go from, for example, a 1 character column under CSV, to a 5 character column that gets "copied" around without losing its formatting? I'm pretty sure my way won't work for an executive.

I'm still not getting the problem. As I understand, Working Pivot tables is just a staging between the Combined worksheet and the Summary worksheet and charts. Your executive shouldn't care a monkey's what Combined and Working Pivot Tables look like (I would even hide them), only Summary. And on Summary, District and Building shows as 5 chars, ISD can be formatted same.

Bob Phillips
08-08-2014, 02:37 AM
An update. I injected all your code. When I select an ISD, District, and School Bldg (doesn't matter which combination), I get a run-time error 1004: ## is not an item of this field. The line below in red is always the culprit.

Public Function FilterPivot( _
ByVal PivotTable As String, _
ByVal ISDCode As String, _
ByVal DistrictCode As String, _
ByVal BuildingCode As String) As Boolean
Dim pvtItem As PivotItem

Application.ScreenUpdating = False

With Worksheets("Working Pivot Tables").PivotTables(PivotTable)

.PivotFields("ISDCode").EnableMultiplePageItems = False
.PivotFields("DistrictCode").EnableMultiplePageItems = False
.PivotFields("BuildingCode").EnableMultiplePageItems = False

With .PageRange

.Cells(1, 2).Value = ISDCode
.Cells(2, 2).Value = DistrictCode
.Cells(3, 2).Value = BuildingCode

I was testing with Oakland Schools/Oakland Schools or Birmingham/any building or no building and it all worked fine. What values are you using, I will try those on mine see if it makes a difference. As a last resort, I can post my workbook somewhere.

dovermac
08-08-2014, 04:03 AM
I tried Oakland Schools, etc like you and got the same thing. I did mention to my project leader your recommendations and he replied with -
"We don't want to deslect the blank from the pivot tables because that is ensuring that we are working with the district summary record and not the building records which is what we want in this case.

On the EnrollmentByGrade pivot table the requirements are to show only the current school year in the graph so the school year is required."

Not sure if that matters or not. As for the working pivot thing, I don't know if the exec will use that or not, but for now, let's skip it. Did you catch my last post about somehow automating the input of CSV files into this workbook and converting those 3 columns to 5 characters? I can't have the superintendent manually formatting these columns every time. You know that won't fly ;-)
P.S. Almost forgot, is there a way to change the display name on the summary page to match what was chosen? I didn't code that, but was curious.

Bob Phillips
08-08-2014, 06:11 AM
I tried Oakland Schools, etc like you and got the same thing. I did mention to my project leader your recommendations and he replied with -
"We don't want to deslect the blank from the pivot tables because that is ensuring that we are working with the district summary record and not the building records which is what we want in this case.

That is not what I meant. What I was saying is that the charts are showing blank entries, which have no values. They are irrelevant, create a datapoint on the series, which obscures a little. Best to just filter it in the pivots.


On the EnrollmentByGrade pivot table the requirements are to show only the current school year in the graph so the school year is required."

Okay, but how does the current school year get selected, it isn't on the selection form?


Did you catch my last post about somehow automating the input of CSV files into this workbook and converting those 3 columns to 5 characters? I can't have the superintendent manually formatting these columns every time. You know that won't fly ;-)

I did respond to that in a separate thread as well, but I think I am still missing it.


Almost forgot, is there a way to change the display name on the summary page to match what was chosen? I didn't code that, but was curious.

Which display name are you referring to?

dovermac
08-08-2014, 06:47 AM
That is not what I meant. What I was saying is that the charts are showing blank entries, which have no values. They are irrelevant, create a datapoint on the series, which obscures a little. Best to just filter it in the pivots.

I'll forward this to the PM.


Okay, but how does the current school year get selected, it isn't on the selection form?

I'll run this by my PM. Not my call.


I did respond to that in a separate thread as well, but I think I am still missing it.

This kind of lost me. Is it still confusing? I'm sure I'm probably explaining it poorly. Did you take a look at the source CSV file from the link I sent? My way of formatting the 3 columns and putting it into the workbook is inefficient I know.


Which display name are you referring to?

The title at the top of the Summary tab in the black bar. Or does your workbook already accurately display the name of whatever you picked in the PS form like Oakland Schools, etc?[/QUOTE]

Bob Phillips
08-08-2014, 09:19 AM
I did respond to that in a separate thread as well, but I think I am still missing it.

This kind of lost me. Is it still confusing? I'm sure I'm probably explaining it poorly. Did you take a look at the source CSV file from the link I sent? My way of formatting the 3 columns and putting it into the workbook is inefficient I know.

I did look, but it doesn't help me I feel. I understand how the data arrives, I understand how it gets changed when you post to Combined, but I don't understand where it is showing as a problem. As I say, Summary only has a short ISD number, and that is easily fixed.



Which display name are you referring to?

The title at the top of the Summary tab in the black bar. Or does your workbook already accurately display the name of whatever you picked in the PS form like Oakland Schools, etc?

Okay, I understand now. Replace the userform call with this code


Public Sub CallUserForm()
Dim mpForm As ParameterSelection
Dim wsCombined As Worksheet
Dim mpTotalsRow As Long
Dim mpTotal As Double

Set wsCombined = Worksheets("Combined")

Set mpForm = New ParameterSelection
With mpForm

.Show
If Not .Cancel Then

Call FilterPivot("EnrollmentByGrade", .ISDCode, .DistrictCode, .BuildingCode)
Call FilterPivot("TotalEnrollmentTrend", .ISDCode, .DistrictCode, .BuildingCode)
Call FilterPivot("PivotTable1", .ISDCode, .DistrictCode, .BuildingCode) 'Race/Ethicity Makeup Trend
Call FilterPivot("PivotTable2", .ISDCode, .DistrictCode, .BuildingCode) 'Other Demographic Enrollment Trend

Worksheets("Summary").Range("B3").Value = .ISDCode
Worksheets("Summary").Range("B4").Value = .DistrictCode
Worksheets("Summary").Range("B5").Value = .BuildingCode
If .ISDCode = NoSelection Or .DistrictCode = NoSelection Or .BuildingCode = NoSelection Then

Worksheets("Summary").Range("B6:D8").ClearContents
ElseIf .BuildingCode <> NoSelection Then

mpTotalsRow = Worksheets("EEM").Columns(colEEM.BuildingCode).Find(.BuildingCode, After:=Worksheets("EEM").Cells(1, colEEM.BuildingCode)).Row
Worksheets("Summary").Range("B6").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.Address)
Worksheets("Summary").Range("B7").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.City) & " " & _
Worksheets("EEM").Cells(mpTotalsRow, colEEM.State) & " " & _
Worksheets("EEM").Cells(mpTotalsRow, colEEM.Zip)
Worksheets("Summary").Range("B8").Value = Worksheets("EEM").Cells(mpTotalsRow, colEEM.Phone)
End If

If .BuildingCode <> NoSelection Then

mpTotalsRow = wsCombined.Columns(colCombined.BuildingCode).Find(.BuildingCode, After:=wsCombined.Cells(1, colCombined.BuildingCode)).Row
ElseIf .DistrictCode <> NoSelection Then

mpTotalsRow = wsCombined.Columns(colCombined.DistrictCode).Find(.DistrictCode, After:=wsCombined.Cells(1, colCombined.DistrictCode)).Row
Else

mpTotalsRow = wsCombined.Columns(colCombined.ISDCode).Find(.ISDCode, After:=wsCombined.Cells(1, colCombined.ISDCode)).Row
End If

With wsCombined

mpTotal = .Cells(mpTotalsRow, colCombined.TotalEnrol).Value
Worksheets("Summary").Range("H3").Value = .Cells(mpTotalsRow, colCombined.American).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I3").Value = .Cells(mpTotalsRow, colCombined.American).Value / mpTotal
Else
Worksheets("Summary").Range("I3").Value = 0
End If
Worksheets("Summary").Range("H4").Value = .Cells(mpTotalsRow, colCombined.Asian).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I4").Value = .Cells(mpTotalsRow, colCombined.Asian).Value / mpTotal
Else
Worksheets("Summary").Range("I4").Value = 0
End If
Worksheets("Summary").Range("H5").Value = .Cells(mpTotalsRow, colCombined.African).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I5").Value = .Cells(mpTotalsRow, colCombined.African).Value / mpTotal
Else
Worksheets("Summary").Range("I5").Value = 0
End If
Worksheets("Summary").Range("H6").Value = .Cells(mpTotalsRow, colCombined.Hispanic).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I6").Value = .Cells(mpTotalsRow, colCombined.Hispanic).Value / mpTotal
Else
Worksheets("Summary").Range("I6").Value = 0
End If
Worksheets("Summary").Range("H7").Value = .Cells(mpTotalsRow, colCombined.Hawaiian).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I7").Value = .Cells(mpTotalsRow, colCombined.Hawaiian).Value / mpTotal
Else
Worksheets("Summary").Range("I7").Value = 0
End If
Worksheets("Summary").Range("H8").Value = .Cells(mpTotalsRow, colCombined.White).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I8").Value = .Cells(mpTotalsRow, colCombined.White).Value / mpTotal
Else
Worksheets("Summary").Range("I8").Value = 0
End If
Worksheets("Summary").Range("H9").Value = .Cells(mpTotalsRow, colCombined.TwoOrMore).Value
If mpTotal <> 0 Then
Worksheets("Summary").Range("I9").Value = .Cells(mpTotalsRow, colCombined.TwoOrMore).Value / mpTotal
Else
Worksheets("Summary").Range("I9").Value = 0
End If
End With

Worksheets("Summary").Range("A1").Value = wsCombined.Cells(mpTotalsRow, colCombined.ISDName).Value & _
IIf(.DistrictCode = NoSelection, "", ", " & wsCombined.Cells(mpTotalsRow, colCombined.DistrictName).Value) & _
IIf(.BuildingCode = NoSelection, "", ", " & wsCombined.Cells(mpTotalsRow, colCombined.BuildingName).Value)
End If
End With
End Sub

dovermac
08-08-2014, 09:30 AM
Ok, well, I still have the same error on line:
.Cells(1, 2).Value = ISDCode
So somewhere my code doesn't quite match up, perhaps on another tab? What was this code supposed to do exactly? I mean what adjustment was made?
Was this supposed to address the columns issue? If so, that would be so sweet.

dovermac
08-08-2014, 04:40 PM
I spoke to my PM and he said to just do whatever you recommend. If you can tell me how to tweak these pivot tables I will. Remember, I suck at these things. :-)

dovermac
08-11-2014, 06:45 AM
We need to figure out what I can do for you. I have to do something for all your help. By the way, my name is Jeff.

Bob Phillips
08-11-2014, 07:15 AM
Hello Jeff, my name is Bob.

I have copied my file to DropBox, https://www.dropbox.com/s/pe70ja36dl8jt64/MDE_Executive_Dashboard.xlsm.

Download it, see if it solves your problems, and let me know what you think, whether anything is not what you need.

dovermac
08-11-2014, 07:22 AM
I'm at work Bob, and that's blocked, like most things here so as soon as I get home I'll try it out. Got any hobbies Bob? I'm personally into movies, music and games.

dovermac
08-11-2014, 02:15 PM
Hi Bob,
I just looked at your workbook. I'm impressed, looks great. We're just about there. Only one thing left. For the sake of this project's demo, we have to show importing 3 different files with the other user form (Data Acquisition), which is next to the PS form in the WB. That form is very basic. All you do is click Open, navigate to the file and then on top box, click the drop down arrow and pick a tab name. We are only going to be using Combined, StudentCount, and EEM. Now the source filename is something like a6578e05-0ec4-4b27-8323-c2836dacceda.csv. It then copies the contents to that tab, starting with the first blank line. My question is can you revise the existing code to somehow import these 3 files depending which one it is and convert the code columns to 5 characters? If you can get that working, that would be it! Then we need to figure out what I can do for you. :-) By the way, where are you located? I'm in Michigan as you probably guessed.

Bob Phillips
08-11-2014, 02:54 PM
Jeff,

Are you saying that you just want to complete the Data Acquisition form take-on of data? open the file, clear out the old, insert the new? Or are you saying append to the data already there? Have you got a sample file that I can test with.

BTW, how are you proposing to fire these forms?

dovermac
08-11-2014, 03:26 PM
The form has been coded, but isn't working exactly right. The files will always append. That part is working. The "code" columns are not converting to 5 characters. The source filenames are gibberish so that doesn't help. Here are links to 3 sample files. Download them, don't rename them and experiment. Try the Data Acquisition Form. It will append just fine, it doesn't convert the 3 code columns to 5 chars.
EEM: https://downloads.mischooldata.org/GeneratedDataFile?filename=226ef227-e6ae-468e-8351-7a416b15ac36.csv (https://www.google.com/url?q=https%3A%2F%2Fdownloads.mischooldata.org%2FGeneratedDataFile%3Ffilena me%3D226ef227-e6ae-468e-8351-7a416b15ac36.csv&sa=D&sntz=1&usg=AFQjCNGlPLi_-FHlCmlvxLxkA4rALxAkaA)
Student Count: https://downloads.mischooldata.org/GeneratedDataFile?filename=6cc33dc0-b63f-46c3-b595-83462cb9d33d.csv
(https://www.google.com/url?q=https%3A%2F%2Fdownloads.mischooldata.org%2FGeneratedDataFile%3Ffilena me%3D6cc33dc0-b63f-46c3-b595-83462cb9d33d.csv&sa=D&sntz=1&usg=AFQjCNG8tax_WT-ep37EDdAKmWtdBGLZ5A)https://downloads.mischooldata.org/GeneratedDataFile?filename=44577f82-18a0-4c3f-b0f0-2a48d5de0da7.csv (https://www.google.com/url?q=https%3A%2F%2Fdownloads.mischooldata.org%2FGeneratedDataFile%3Ffilena me%3D44577f82-18a0-4c3f-b0f0-2a48d5de0da7.csv&sa=D&sntz=1&usg=AFQjCNH6gH37fhM_tc6lBJkPg0_mF0CMRQ)
(https://www.google.com/url?q=https%3A%2F%2Fdownloads.mischooldata.org%2FGeneratedDataFile%3Ffilena me%3D44577f82-18a0-4c3f-b0f0-2a48d5de0da7.csv&sa=D&sntz=1&usg=AFQjCNH6gH37fhM_tc6lBJkPg0_mF0CMRQ)This is the Combined File.

I don't understand the "how am I to fire these forms" question. can you elaborate please?

dovermac
08-15-2014, 03:41 AM
Hey Bob,
Everything ok? Just curious. You need anything from me?

Jeff

dovermac
08-21-2014, 05:26 PM
Hi Bob,
I'm guessing that you're no longer interested in working on this? If that's the case, just let me know. No hard feelings. I really appreciate all your help, sincerely! :-)

Jeff