fCode for Prompt 2
Sub CreateDashboardCards( )
Dim ws As Worksheet
Dim card As Shape
Dim topPosition As Double
Dim leftPosition As Double
' Create a new worksheet called "Dashboard"
Set ws = ThisWorkbook.Sheets("Dashboard")
If Not ws Is Nothing Then
Application.DisplayAlerts = False
ws.Delete
Application.DisplayAlerts = True
End If
Set ws = ThisWorkbook.Sheets.Add
ws.Name = "Dashboard"
' Format sheet: Remove gridlines and set background color
With ws
.Cells.Interior.Color = RGB(217, 217, 217) ' Set background color
End With
' Hide gridlines (using ActiveWindow method for Excel 2013)
ActiveWindow.DisplayGridlines = False
' Card 1 to Card 6 (Row 5)
topPosition = 72 ' Start from row 5, which is about 72 pixels
leftPosition = 12 ' Start with 12 pixels from the left for the first card
' Card 1
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 1.65 * 72, 0.75 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255) ' White fill
card.Line.Visible = msoFalse ' No border
card.Adjustments.Item(1) = 0.05 ' Border radius
card.Name = "cfilters"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 1.65 * 72 + 12 ' Update left position with margin
' Card 2
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2# * 72, 0.75 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.05
card.Name = "ctsales"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2# * 72 + 12
' Card 3
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2# * 72, 0.75 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.05
card.Name = "ctmargin"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2# * 72 + 12
' Card 4
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2# * 72, 0.75 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.05
card.Name = "cpmargin"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2# * 72 + 12
' Card 5
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 3.8 * 72, 0.75 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.05
card.Name = "ccustcount"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 3.8 * 72 + 12
' Card 6
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2.5 * 72, 5.3 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.05
card.Name = "ctop10"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2.5 * 72 + 12
' Card 7 to Card 9 (Row 6)
topPosition = topPosition + 2.1 * 72 + 12 ' Move to next row
leftPosition = 12 ' Reset left position
' Card 7
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 6.6 * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "csalestrend"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 6.6 * 72 + 12
' Card 8
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2.6 * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "ccustsource"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2.6 * 72 + 12
' Card 9
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2.6 * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "csalescity"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2.6 * 72 + 12
' Card 10 to Card 12 (Row 7)
topPosition = topPosition + 2.1 * 72 + 12 ' Move to next row
leftPosition = 12 ' Reset left position
' Card 10
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 4.1 * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "csalesservice"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 4.1 * 72 + 12
' Card 11
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 2.5 * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "cdeptmargin"
card.Top = topPosition
card.Left = leftPosition
leftPosition = leftPosition + 2.5 * 72 + 12
' Card 12
Set card = ws.Shapes.AddShape(msoShapeRoundedRectangle, leftPosition, topPosition, 5# * 72, 2.1 * 72)
card.Fill.BackColor.RGB = RGB(255, 255, 255)
card.Line.Visible = msoFalse
card.Adjustments.Item(1) = 0.03
card.Name = "cnewrepeat"
card.Top = topPosition
card.Left = leftPosition
End Sub
Code for Prompt 3
On Error Resume NextSub GeneratePivotTables()
Dim wsData As Worksheet
Dim wsPivot As Worksheet
Dim ptCache As PivotCache
Dim pt As PivotTable
Dim startRow As Long
' Set references to sheets
Set wsData = ThisWorkbook.Sheets("Data")
Set wsPivot = ThisWorkbook.Sheets("Pivot")
' Clear existing pivot tables on the Pivot sheet
wsPivot.Cells.Clear
' Set the starting row for placing pivot tables
startRow = 1
' Create Pivot Table 1: totalsales
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="totalsales")
With pt
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 2: totalmargin
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="totalmargin")
With pt
.AddDataField .PivotFields("Margin Amount"), "Sum of Margin Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 3: customerscount
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="customerscount")
With pt
.PivotFields("Sale Type").Orientation = xlRowField
.AddDataField .PivotFields("Customer Name"), "Count of Customer Name", xlCount
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 4: totalmargin (again)
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="totalmargin2")
With pt
.AddDataField .PivotFields("Margin Amount"), "Sum of Margin Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 5: salestrend
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="salestrend")
With pt
.PivotFields("Year").Orientation = xlRowField
.PivotFields("Month").Orientation = xlRowField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 6: customersource
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="customersource")
With pt
.PivotFields("Year").Orientation = xlRowField
.PivotFields("Customer Source").Orientation = xlColumnField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 7: salesbycity
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="salesbycity")
With pt
.PivotFields("City").Orientation = xlRowField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 8: top10
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="top10")
With pt
.PivotFields("Customer Name").Orientation = xlRowField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 9: salesbyservice
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="salesbyservice")
With pt
.PivotFields("Service").Orientation = xlRowField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 10: departmentmargin
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="departmentmargin")
With pt
.PivotFields("Department").Orientation = xlRowField
.AddDataField .PivotFields("Margin Amount"), "Sum of Margin Amount", xlSum
End With
startRow = startRow + pt.TableRange2.Rows.Count + 2
' Create Pivot Table 11: newvsrepeat
Set ptCache = ThisWorkbook.PivotCaches.Create(SourceType:=xlDatabase,
sourceData:=wsData.ListObjects("salesdata").Range)
Set pt = ptCache.CreatePivotTable(TableDestination:=wsPivot.Cells(startRow, 1),
TableName:="newvsrepeat")
With pt
.PivotFields("Year").Orientation = xlRowField
.PivotFields("Month").Orientation = xlRowField
.PivotFields("Sale Type").Orientation = xlColumnField
.AddDataField .PivotFields("Sales Amount"), "Sum of Sales Amount", xlSum
End With
MsgBox "Pivot tables created successfully!", vbInformation
End Sub
Code for Prompt 4
Public Sub CreateDashboardCharts()
On Error Resume Next
Dim wsP As Worksheet
Dim wsD As Worksheet
Dim pt As PivotTable
Dim shp As Shape
Dim cht As ChartObject
Set wsP = ThisWorkbook.Sheets("Pivot")
Set wsD = ThisWorkbook.Sheets("Dashboard")
' Delete existing charts on Dashboard sheet
For Each cht In wsD.ChartObjects
cht.Delete
Next cht
' 1. Sales Trend Chart
Set pt = wsP.PivotTables("salestrend")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("csalestrend").Left + (wsD.Shapes("csalestrend").width * 0.05), _
Top:=wsD.Shapes("csalestrend").Top + (wsD.Shapes("csalestrend").height * 0.1), _
width:=wsD.Shapes("csalestrend").width * 0.9, _
height:=wsD.Shapes("csalestrend").height * 0.8)
With cht.Chart
.ChartType = xlLineMarkers
.SetSourceData pt.TableRange1
.ChartTitle.Delete
With .SeriesCollection(1)
.Format.Line.Weight = 1.75
.Format.Line.ForeColor.RGB = RGB(0, 32, 96)
.MarkerBackgroundColor = RGB(255, 255, 255)
.MarkerForegroundColor = RGB(0, 32, 96)
.MarkerSize = 5
.HasDropLines = True
.MarkerStyle = xlMarkerStyleCircle
End With
Call FormatChartGeneral(cht.Chart)
End With
' 2. Customer Source Chart
Set pt = wsP.PivotTables("customersource")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("ccustsource").Left + (wsD.Shapes("ccustsource").width * 0.05), _
Top:=wsD.Shapes("ccustsource").Top + (wsD.Shapes("ccustsource").height * 0.1), _
width:=wsD.Shapes("ccustsource").width * 0.9, _
height:=wsD.Shapes("ccustsource").height * 0.8)
With cht.Chart
.ChartType = xlBarStacked100
.SetSourceData pt.TableRange1
Dim i As Long
For i = 1 To .SeriesCollection.Count
.SeriesCollection(i).Format.Fill.ForeColor.RGB = RGB(0, 32 + (i * 32), 96 + (i * 32))
Next i
Call FormatChartGeneral(cht.Chart)
End With
' 3. Sales by City Chart
Set pt = wsP.PivotTables("salesbycity")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("csalescity").Left + (wsD.Shapes("csalescity").width * 0.05), _
Top:=wsD.Shapes("csalescity").Top + (wsD.Shapes("csalescity").height * 0.1), _
width:=wsD.Shapes("csalescity").width * 0.9, _
height:=wsD.Shapes("csalescity").height * 0.8)
With cht.Chart
.ChartType = xlDoughnut
.SetSourceData pt.TableRange1
.ChartTitle.Delete
For i = 1 To .SeriesCollection(1).Points.Count
.SeriesCollection(1).Points(i).ExplosionOffset = 3
.SeriesCollection(1).Points(i).Format.Fill.ForeColor.RGB = RGB(0, 32 + (i * 16), 96 + (i * 16))
Next i
Call FormatChartGeneral(cht.Chart)
End With
' 4. Top 10 Chart
Set pt = wsP.PivotTables("top10")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("ctop10").Left + (wsD.Shapes("ctop10").width * 0.05), _
Top:=wsD.Shapes("ctop10").Top + (wsD.Shapes("ctop10").height * 0.1), _
width:=wsD.Shapes("ctop10").width * 0.9, _
height:=wsD.Shapes("ctop10").height * 0.8)
With cht.Chart
.ChartType = xlBarClustered
.SetSourceData pt.TableRange1
.SeriesCollection(1).Format.Fill.ForeColor.RGB = RGB(0, 32, 96)
.ChartTitle.Delete
Call FormatChartGeneral(cht.Chart)
End With
' 5. Sales by Service Chart
Set pt = wsP.PivotTables("salesbyservice")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("csalesservice").Left + (wsD.Shapes("csalesservice").width * 0.05), _
Top:=wsD.Shapes("csalesservice").Top + (wsD.Shapes("csalesservice").height * 0.1), _
width:=wsD.Shapes("csalesservice").width * 0.9, _
height:=wsD.Shapes("csalesservice").height * 0.8)
With cht.Chart
.ChartType = xl3DColumn
.SetSourceData pt.TableRange1
.SeriesCollection(1).Format.Fill.ForeColor.RGB = RGB(0, 32, 96)
.RightAngleAxes = True
Call FormatChartGeneral(cht.Chart)
.ChartTitle.Delete
End With
' 6. Department Margin Chart
Set pt = wsP.PivotTables("departmentmargin")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("cdeptmargin").Left + (wsD.Shapes("cdeptmargin").width * 0.05), _
Top:=wsD.Shapes("cdeptmargin").Top + (wsD.Shapes("cdeptmargin").height * 0.1), _
width:=wsD.Shapes("cdeptmargin").width * 0.9, _
height:=wsD.Shapes("cdeptmargin").height * 0.8)
With cht.Chart
.ChartType = xlPie
.SetSourceData pt.TableRange1
.ChartTitle.Delete
For i = 1 To .SeriesCollection(1).Points.Count
.SeriesCollection(1).Points(i).ExplosionOffset = 3
.SeriesCollection(1).Points(i).Format.Fill.ForeColor.RGB = RGB(0, 32 + (i * 16), 96 + (i * 16))
Next i
Call FormatChartGeneral(cht.Chart)
End With
' 7. New vs Repeat Chart
Set pt = wsP.PivotTables("newvsrepeat")
Set cht = wsD.ChartObjects.Add( _
Left:=wsD.Shapes("cnewrepeat").Left + (wsD.Shapes("cnewrepeat").width * 0.05), _
Top:=wsD.Shapes("cnewrepeat").Top + (wsD.Shapes("cnewrepeat").height * 0.1), _
width:=wsD.Shapes("cnewrepeat").width * 0.9, _
height:=wsD.Shapes("cnewrepeat").height * 0.8)
With cht.Chart
.ChartType = xlLineMarkersStacked
.SetSourceData pt.TableRange1
.ChartTitle.Delete
For i = 1 To .SeriesCollection.Count
With .SeriesCollection(i)
.Format.Line.ForeColor.RGB = RGB(0, 32 + (i * 32), 96 + (i * 32))
.Format.Line.Weight = 1.5
.MarkerBackgroundColor = RGB(255, 255, 255)
.MarkerForegroundColor = RGB(0, 32 + (i * 32), 96 + (i * 32))
.MarkerSize = 4
.MarkerStyle = xlMarkerStyleCircle
.Border.Weight = 2
End With
Next i
Call FormatChartGeneral(cht.Chart)
End With
MsgBox "Charts have been created successfully!", vbInformation
End Sub
Private Sub FormatChartGeneral(cht As Chart)
With cht
.HasTitle = False
.HasLegend = False
' Format chart area
With .ChartArea
.Format.Fill.Visible = False
.Format.Line.Visible = False
End With
' Format plot area
.PlotArea.Format.Line.Visible = False
' Format axes if they exist
On Error Resume Next
With .Axes(xlCategory)
.Format.Line.Visible = False
.TickLabels.Font.Name = "Calibri"
.TickLabels.Font.Size = 7
.TickLabels.Font.Bold = True
.TickLabels.Font.Color = RGB(0, 32, 96)
End With
With .Axes(xlValue)
.TickLabels.Format.Line.Visible = False
.TickLabels.Font.Name = "Calibri"
.TickLabels.Font.Size = 7
.TickLabels.Font.Bold = True
.TickLabels.Font.Color = RGB(0, 32, 96)
.NumberFormat = "#,##0"
End With
On Error GoTo 0
' Hide field buttons
.ShowAllFieldButtons = False
End With
End Sub