library(dplyr)
##
## Attaching package: 'dplyr'
## The following objects are masked from 'package:stats':
##
## filter, lag
## The following objects are masked from 'package:base':
##
## intersect, setdiff, setequal, union
library(readr)
library(ggplot2)
library(ggmosaic)
data = read_csv("C:\\Users\\MUTHI'AH IFFA\\Downloads\\Semester 4\\Komstat\\StudentPerformanceFactors.csv", show_col_types = FALSE)
# Memfilter data berdasarkan gender
data_gender = data %>% filter(Gender %in% c("Female", "Male"))
# Membuat boxplot
ggplot(data_gender,
aes(x = Extracurricular_Activities,
y = Exam_Score,
fill = Gender)) +
geom_boxplot() +
scale_fill_manual(values = c("Female" = "salmon", "Male" = "lightblue")) +
labs(title = "Exam Score Female VS Male",
x = "Partisipasi Extracurricular",
y = "Exam Score") +
theme_minimal()
# Memfilter data berdasarkan gender
data_school = data %>% filter(School_Type %in% c("Public", "Private"))
#Membuat Boxplot
ggplot(data_school,
aes(x = School_Type,
y = Exam_Score, fill = School_Type)) +
geom_boxplot() +
scale_fill_manual(values = c("Public" = "blue", "Private" = "red")) +
labs(title = "Exam Score Public School vs Private School",
x = "School Type",
y = "Exam Score") +
theme_minimal()
ggplot(data,
aes(x = Hours_Studied,
y = Exam_Score,
color = Gender)) +
geom_point(alpha = 0.8) +
scale_color_manual(values = c("Female" = "salmon", "Male" = "lightblue")) +
labs(title = "Korelasi Nilai dengan Lama Belajar (berdasarkan Gender)",
x = "Hours Studied",
y = "Exam Score") +
theme_minimal()
ggplot(data,
aes(x = Motivation_Level,
y = Exam_Score,
fill = Parental_Involvement)) +
geom_boxplot() +
labs(title = "Exam Score Berdasarkan Motivation Level dan Parental Involvement",
x = "Motivation Level",
y = "Exam Score") +
theme_minimal()
ggplot(data) +
geom_mosaic(
aes(weight = 1,
x = product(School_Type,
Teacher_Quality),
fill = Teacher_Quality)) +
scale_fill_manual(values = c("Low" = "red",
"Medium" = "yellow",
"High" = "forestgreen")) +
labs(title = "Proporsi Teacher Quality Public School vs Private School",
x = "School Type",
y = "Teacher Quality") +
theme_minimal()
## Warning: The `scale_name` argument of `continuous_scale()` is deprecated as of ggplot2
## 3.5.0.
## This warning is displayed once every 8 hours.
## Call `lifecycle::last_lifecycle_warnings()` to see where this warning was
## generated.
## Warning: The `trans` argument of `continuous_scale()` is deprecated as of ggplot2 3.5.0.
## ℹ Please use the `transform` argument instead.
## This warning is displayed once every 8 hours.
## Call `lifecycle::last_lifecycle_warnings()` to see where this warning was
## generated.
## Warning: `unite_()` was deprecated in tidyr 1.2.0.
## ℹ Please use `unite()` instead.
## ℹ The deprecated feature was likely used in the ggmosaic package.
## Please report the issue at <https://github.com/haleyjeppson/ggmosaic>.
## This warning is displayed once every 8 hours.
## Call `lifecycle::last_lifecycle_warnings()` to see where this warning was
## generated.
ggplot(data,
aes(x = Teacher_Quality,
y = Exam_Score,
fill = School_Type)) +
geom_boxplot() +
labs(title = "Exam Score Berdasarkan Teacher Quality dan School Type",
x = "Teacher Quality",
y = "Exam Score") +
theme_minimal()
library(ggplot2)
ggplot(data, aes(x = Previous_Scores)) +
geom_histogram(binwidth = 5, fill = "blue", color = "black", alpha = 0.7) +
theme_minimal() +
labs(title = "Distribusi Previous Scores",
x = "Previous Scores", y = "Frekuensi")
ggplot(data, aes(x = Exam_Score)) +
geom_histogram(binwidth = 5, fill = "red", color = "cornsilk3", alpha = 0.7) +
theme_minimal() +
labs(title = "Distribusi Exam Scores",
x = "Exam Scores", y = "Frekuensi")
library(ggplot2)
library(dplyr)
# Membuat kategori Tutoring Sessions
data <- data %>%
mutate(Tutoring_Category = ifelse(Tutoring_Sessions %in% c(0, 1), "Rendah (0-1 sesi)", "Tinggi (2-3 sesi)"))
# Menghitung rata-rata Previous Scores dan Exam Scores dalam setiap kategori
agg_data <- data %>%
group_by(Tutoring_Category) %>%
summarise(Avg_Previous_Scores = mean(Previous_Scores),
Avg_Exam_Scores = mean(Exam_Score))
# Mengubah data ke format long untuk ggplot
agg_data_long <- tidyr::pivot_longer(agg_data, cols = c(Avg_Previous_Scores, Avg_Exam_Scores),
names_to = "Score_Type", values_to = "Avg_Score")
# Bar chart dengan kategori Tutoring Sessions
ggplot(agg_data_long, aes(x = Tutoring_Category, y = Avg_Score, fill = Score_Type)) +
geom_bar(stat = "identity", position = "dodge") +
theme_minimal() +
labs(title = "Rata-Rata Previous Scores dan Exam Scores",
x = "Tutoring Sessions", y = "Rata-Rata Skor") +
scale_fill_manual(values = c("Avg_Previous_Scores" = "blue", "Avg_Exam_Scores" = "red"))
a. Buat Class System S4 dengan nama “Mahasiswa” yang berisi atribut :
nama (char)
NIM (char)
domisili (char)
#membuat coords menjadi class
setClass("coords",
representation(x = "numeric", y = "numeric"))
setClass("Mahasiswa",
representation(
Nama = "character",
NIM = "character",
Domisili = "character"
))
b. Buat objek dalam class “Mahasiswa” sebanyak 5 individu
# Buat objek untuk lima individu
Mhs1 <- new("Mahasiswa", Nama = "Iffa", NIM = "G1401231091", Domisili = "Bandung")
Mhs2 <- new("Mahasiswa", Nama = "Fatima", NIM = "G1401231036", Domisili = "Tajur")
Mhs3 <- new("Mahasiswa", Nama = "Agustin", NIM = "G1401231105", Domisili = "Purwodadi")
Mhs4 <- new("Mahasiswa", Nama = "Qindy", NIM = "G1401231035", Domisili = "Jonggol")
Mhs5 <- new("Mahasiswa", Nama = "Azzah", NIM = "G1401231014", Domisili = "Jakarta")
# Periksa objek yang telah dibuat
show(Mhs1)
## An object of class "Mahasiswa"
## Slot "Nama":
## [1] "Iffa"
##
## Slot "NIM":
## [1] "G1401231091"
##
## Slot "Domisili":
## [1] "Bandung"
show(Mhs2)
## An object of class "Mahasiswa"
## Slot "Nama":
## [1] "Fatima"
##
## Slot "NIM":
## [1] "G1401231036"
##
## Slot "Domisili":
## [1] "Tajur"
show(Mhs3)
## An object of class "Mahasiswa"
## Slot "Nama":
## [1] "Agustin"
##
## Slot "NIM":
## [1] "G1401231105"
##
## Slot "Domisili":
## [1] "Purwodadi"
show(Mhs4)
## An object of class "Mahasiswa"
## Slot "Nama":
## [1] "Qindy"
##
## Slot "NIM":
## [1] "G1401231035"
##
## Slot "Domisili":
## [1] "Jonggol"
show(Mhs5)
## An object of class "Mahasiswa"
## Slot "Nama":
## [1] "Azzah"
##
## Slot "NIM":
## [1] "G1401231014"
##
## Slot "Domisili":
## [1] "Jakarta"
c. Buatlah objek tersebut dengan fungsi konstruktor
setClass("coords",
representation(x = "numeric", y = "numeric"))
restarcoords = function(x, y) {
if (length(x) != length(y))
stop("length x dan y harus bernilai sama")
if (!is.numeric(x) || !is.numeric(y))
stop("x dan y harus vektor numeric")
return(new("coords", x = as.vector(x), y = as.vector(y)))
}
pts <- restarcoords(round(rnorm(5), 2), round(rnorm(5),2))
Mahasiswa = function(Nama, NIM, Domisili) {
# Validasi panjang NIM
if (nchar(NIM) != 11) {
warning("NIM harus berjumlah 11 digit")
}
# Buat dan kembalikan objek S4
return(new("Mahasiswa",
Nama = as.character(Nama),
NIM = as.character(NIM),
Domisili = as.character(Domisili)))
}
Mhs1 = Mahasiswa("Iffa", "G1401231091", "Bandung")
Mhs2 = Mahasiswa("Fatima", "G1401231036", "Tajur")
Mhs3 = Mahasiswa("Agustin", "G1401231105", "Purwodadi")
Mhs4 = Mahasiswa("Qindy", "G1401231035", "Jonggol")
Mhs5 = Mahasiswa("Azzah", "G1401231014", "Jakarta")
d. Ubah method show agar dapat menampilkan objek
setMethod("show", "coords", function(object) {
cat("Koordinat:\n")
cat("x:", paste(object@x, collapse = " "), "\n")
cat("y:", paste(object@y, collapse = " "), "\n")
})
setMethod("show", "Mahasiswa", function(object) {
cat("Data Mahasiswa\n")
cat("Nama :", object@Nama, "\n")
cat("NIM :", object@NIM, "\n")
cat("Domisili :", object@Domisili, "\n")
})
Mhs1
## Data Mahasiswa
## Nama : Iffa
## NIM : G1401231091
## Domisili : Bandung
Mhs2
## Data Mahasiswa
## Nama : Fatima
## NIM : G1401231036
## Domisili : Tajur
Mhs3
## Data Mahasiswa
## Nama : Agustin
## NIM : G1401231105
## Domisili : Purwodadi
Mhs4
## Data Mahasiswa
## Nama : Qindy
## NIM : G1401231035
## Domisili : Jonggol
Mhs5
## Data Mahasiswa
## Nama : Azzah
## NIM : G1401231014
## Domisili : Jakarta
f(𝑥1,𝑥2,𝑥3) = 10 (X1+X2)2+ (2X1+X32)2+(1+X2)2
my_func = function(x) {
x1 = x[1]
x2 = x[2]
x3 = x[3]
return(10 * (x1 + x2)^2 + (2 * x1 + x3^2) + (1 + x2)^2)
}
# Menjalankan optimisasi dengan metode Nelder-Mead
result = optim(c(0, 0, 0), my_func, method = "Nelder-Mead")
# Menampilkan hasil optimasi
result$par # Nilai optimal untuk x1, x2, x3
## [1] -1.000313e-01 3.772963e-05 -8.259502e-06
result$value # Nilai minimum dari fungsi
## [1] 0.9
# Membuat Class S3 "Optimasi"
Optimasi = function(nama_metode, fungsi) {
obj = list(
nama_metode = nama_metode,
fungsi = fungsi
)
class(obj) = "Optimasi"
return(obj)
}
# Method untuk mengeksekusi optimasi
execute.Optimasi = function(obj, initial_values) {
if (!inherits(obj, "Optimasi")) stop("Objek bukan dari class 'Optimasi'")
result <- optim(initial_values, obj$fungsi, method = obj$nama_metode)
return(list(
optimal_values = result$par,
minimum_value = result$value
))
}
# Contoh Penggunaan
fungsi = function(x) {
x1 = x[1]
x2 = x[2]
x3 = x[3]
return(10 * (x1 + x2)^2 + (2 * x1 + x3^2) + (1 + x2)^2)
}
optimasi_obj = Optimasi("Nelder-Mead", my_func)
hasil = execute.Optimasi(optimasi_obj, c(0, 0, 0))
# Menampilkan hasil optimasi
hasil
## $optimal_values
## [1] -1.000313e-01 3.772963e-05 -8.259502e-06
##
## $minimum_value
## [1] 0.9