Skip to content

Commit

Permalink
Merge pull request #775 from gjwgit/zy/760_evaluate_rpart_hand
Browse files Browse the repository at this point in the history
zy/760 EVALUATE: rpart hand as the template for other methods
  • Loading branch information
gjwgit authored Jan 14, 2025
2 parents cc0d918 + 3f206c7 commit 3f29103
Show file tree
Hide file tree
Showing 23 changed files with 209 additions and 154 deletions.
16 changes: 2 additions & 14 deletions assets/r/evaluate_measure_error_matrix.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
# Using `actual` and `predicted` generate error matrix with `rattle::errorMatrix()`.
# Using `actual` and `predicted` generate error matrix.
#
# Copyright (C) 2024, Togaware Pty Ltd.
#
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Monday 2025-01-06 06:59:55 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:16:05 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand All @@ -29,24 +29,12 @@
# References:
#
# @williams:2017:essentials Chapter 7.
# https://survivor.togaware.com/datascience/dtrees.html
# https://survivor.togaware.com/datascience/rpart.html
# https://survivor.togaware.com/datascience/ for further details.

## #########################################################################
## #########################################################################
## #########################################################################
## 20241220 gjw DO NOT MODIFY THIS FILE WITHOUT DISCUSSION
## #########################################################################
## #########################################################################
## #########################################################################

# Load required packages from the local library into the R session.

library(rattle) # Generate an error matrix.

####################################

em_count <- rattle::errorMatrix(actual, predicted, count=TRUE)
##
## 20241229 zy Capture the output of the error matrix and print it to
Expand Down
56 changes: 52 additions & 4 deletions assets/r/evaluate_measure_hand.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,60 @@
# PLACE HOLDER FOR NOW - THE CODE CAME FROM evaluate_model_rpart.R
# Use `actual` and `probability` for David Hand's classifier evaluation.
#
# Copyright (C) 2025, Togaware Pty Ltd.
#
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Friday 2025-01-10 16:03:40 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
# This program is free software: you can redistribute it and/or modify it under
# the terms of the GNU General Public License as published by the Free Software
# Foundation, either version 3 of the License, or (at your option) any later
# version.
#
# This program is distributed in the hope that it will be useful, but WITHOUT
# ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
# FOR A PARTICULAR PURPOSE. See the GNU General Public License for more
# details.
#
# You should have received a copy of the GNU General Public License along with
# this program. If not, see <https://www.gnu.org/licenses/>.
#
# Author: Zheyuan Xu, Graham Williams

# TIMESTAMP
#
# References:
#
# @williams:2017:essentials Chapter 7.
# https://survivor.togaware.com/datascience/ for further details.

# Load required packages from the local library into the R session.

library(glue)
library(hmeasure) # David Hand's classifier performance measure.

# Evaluate the model using HMeasure.

results <- HMeasure(true.class = actual_rpart_labels, scores = predicted_rpart_probs)
results <- hmeasure::HMeasure(true.class = actual, scores = probability)

# Create a single SVG file that displays all 4 plots.

svg(filename = glue("TEMPDIR/model_evaluate_hand_{mtype}_{dtype}.svg"),
width = 11,
height = 8)

# Set up a 2x2 layout.

par(mfrow = c(2, 2))

svg("TEMPDIR/model_rpart_evaluate_hand.svg")
# Generate the four plots in one device.

plotROC(results)
hmeasure::plotROC(results, which = 1,)
hmeasure::plotROC(results, which = 2,)
hmeasure::plotROC(results, which = 3,)
hmeasure::plotROC(results, which = 4,)

dev.off()
8 changes: 2 additions & 6 deletions assets/r/evaluate_measure_roc.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
# Using `actual` and `prediction` to generate ROC/AUC plots.
# Use `actual` and `prediction` to generate ROC/AUC plots.
#
# Copyright (C) 2024, Togaware Pty Ltd.
#
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Monday 2025-01-06 08:23:01 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:16:33 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand All @@ -29,14 +29,10 @@
# References:
#
# @williams:2017:essentials Chapter 7.
# https://survivor.togaware.com/datascience/dtrees.html
# https://survivor.togaware.com/datascience/rpart.html
# https://survivor.togaware.com/datascience/ for further details.

# Load required packages from the local library into the R session.

library(ggplot2, quietly=TRUE)
library(glue)
library(ROCR)

################################
Expand Down
4 changes: 1 addition & 3 deletions assets/r/evaluate_riskchart.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Sunday 2024-12-15 10:48:49 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:21:31 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,8 +35,6 @@

# Load required packages from the local library into the R session.

library(ggtext) # Support markdown in ggplot titles.
library(glue) # Format strings: glue().
library(rattle) # Generate a risk chart.

####################################
Expand Down
4 changes: 1 addition & 3 deletions assets/r/explore_visual_categoric.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Tuesday 2024-12-10 17:23:55 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:23:11 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -33,8 +33,6 @@

# Load required packages from the local library into the R session.

library(ggplot2)

# Preprocess the dataset to generate a temporary dataset `tds` for the
# plots.

Expand Down
10 changes: 4 additions & 6 deletions assets/r/explore_visual_categoric_nogroupby.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Friday 2024-11-29 10:48:54 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:23:50 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,10 +35,8 @@

# Load required packages from the local library into the R session.

library(ggplot2)

########################################################################
# Bar Plot
# Bar Plot
########################################################################

svg("TEMPDIR/explore_visual_bars.svg", width=10)
Expand All @@ -55,7 +53,7 @@ ds %>%
dev.off()

########################################################################
# Dot Plot
# Dot Plot
########################################################################

svg("TEMPDIR/explore_visual_dots.svg", width=10)
Expand Down Expand Up @@ -107,7 +105,7 @@ ggplot(combined_data, aes(y = SELECTED_VAR, x = Frequency)) +
dev.off()

########################################################################
# Mosaic Plot
# Mosaic Plot
########################################################################

## # 20241129 gjw A mosaic plot does not make sense for a single variable.
Expand Down
3 changes: 1 addition & 2 deletions assets/r/explore_visual_numeric.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Tuesday 2024-12-10 17:20:42 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:23:26 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,7 +35,6 @@
# Load required packages from the local library into the R session.

library(dplyr)
library(ggplot2)
library(rattle)

# Preprocess the dataset to generate a temporary dataset `tds` for the
Expand Down
11 changes: 5 additions & 6 deletions assets/r/explore_visual_numeric_nogroupby.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Friday 2024-11-29 08:38:33 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:24:10 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,7 +35,6 @@
# https://survivor.togaware.com/datascience/ for further details.

library(dplyr)
library(ggplot2)
library(rattle)

########################################################################
Expand Down Expand Up @@ -126,7 +125,7 @@ ds %>%
dev.off()

########################################################################
# BENFORD'S LAW
# BENFORD'S LAW
########################################################################

# Initialies the parameters.
Expand Down Expand Up @@ -161,7 +160,7 @@ len <- nchar(as.character(tds[1, 1]))
svg("TEMPDIR/explore_visual_benford.svg", width=10)

p <- ggplot2::ggplot(dsm,
ggplot2::aes_string(x = "digit",
ggplot2::aes_string(x = "digit",
y = "value",
colour = "variable",
shape = "variable")) +
Expand Down Expand Up @@ -189,7 +188,7 @@ dev.off()
# PAIRS - REQUIRES TWO VARIABLES
########################################################################

# Display a pairs plot for the selected variables.
# Display a pairs plot for the selected variables.

# Use GGally's ggpairs() to do the hard work.

Expand All @@ -211,7 +210,7 @@ dev.off()
## ggplot2::theme(panel.grid.major=ggplot2::element_blank(), legend.position="right") +
## ggplot2::xlab(paste("\n\n", "TIMESTAMP", sep=""))


# ggplot2::scale_alpha_continuous(guide=FALSE) +
# ggplot2::scale_fill_brewer(palette=rattlePalette) +
# ggplot2::scale_colour_brewer(palette=rattlePalette)
Expand Down
13 changes: 5 additions & 8 deletions assets/r/model_build_adaboost.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Wednesday 2024-11-27 11:39:42 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:24:26 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand All @@ -21,16 +21,13 @@
# You should have received a copy of the GNU General Public License along with
# this program. If not, see <https://www.gnu.org/licenses/>.
#
# Author: Zheyuan Xu
# Author: Zheyuan Xu, Graham Williams

# Load required libraries.

library(ada)
library(caret)
library(ggplot2)
library(ggtext)
library(hmeasure)
library(rattle)
library(rattle)
library(rpart)

# Define model type and description.
Expand All @@ -48,7 +45,7 @@ ada_control <- rpart.control(maxdepth = BOOST_MAX_DEPTH,
# Train the AdaBoost model.

model_ada <- ada(form,
data = trds,
data = trds,
iter = BOOST_ITERATIONS,
type = "gentle", # Type of boosting.
control = ada_control)
Expand Down Expand Up @@ -108,7 +105,7 @@ ada_plot <- ada_plot +

# Increase plot limits to make space for the labels.

ada_plot <- ada_plot +
ada_plot <- ada_plot +
scale_y_continuous(expand = expansion(mult = c(0, 0.15))) +
expand_limits(y = max(importance_df$Importance) * 1.2)

Expand Down
4 changes: 1 addition & 3 deletions assets/r/model_build_conditional_forest.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Tuesday 2024-12-03 12:39:21 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:22:06 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,8 +35,6 @@

# Load required packages.

library(ggplot2)
library(ggtext) # Support markdown in ggplot titles.
library(kernlab)
library(party)
library(rattle)
Expand Down
4 changes: 1 addition & 3 deletions assets/r/model_build_ctree.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Monday 2024-12-02 08:42:13 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:01:40 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand Down Expand Up @@ -35,8 +35,6 @@

# Load required packages from the local library into the R session.

library(ggtext) # Support markdown in ggplot titles.
library(hmeasure)
library(party) # Conditional inference trees
library(partykit) # Enhanced visualization and interpretation

Expand Down
3 changes: 1 addition & 2 deletions assets/r/model_build_linear.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
# License: GNU General Public License, Version 3 (the "License")
# https://www.gnu.org/licenses/gpl-3.0.en.html
#
# Time-stamp: <Monday 2024-10-07 17:03:05 +1100 Graham Williams>
# Time-stamp: <Friday 2025-01-10 16:22:21 +1100 Graham Williams>
#
# Licensed under the GNU General Public License, Version 3 (the "License");
#
Expand All @@ -24,7 +24,6 @@
#
# Author: Zheyuan Xu

library(ggtext) # Support markdown in ggplot titles.
library(rattle)

# Define model type and description.
Expand Down
Loading

0 comments on commit 3f29103

Please sign in to comment.