GCC Code Coverage Report


Directory: src/athena/
File: athena_accuracy.f90
Date: 2025-12-10 07:37:07
Exec Total Coverage
Lines: 0 0 100.0%
Functions: 0 0 -%
Branches: 0 0 -%

Line Branch Exec Source
1 module athena__accuracy
2 !! Module containing functions to compute the accuracy of a model
3 use coreutils, only: real32
4 implicit none
5
6
7 private
8
9 public :: compute_accuracy_function
10 public :: categorical_score
11 public :: mae_score, mse_score, rmse_score
12 public :: r2_score
13
14
15 abstract interface
16 !! Interface for the accuracy function
17 pure function compute_accuracy_function(predicted, expected) result(output)
18 !! Compute the accuracy of a model
19 import real32
20 real(real32), dimension(:,:), intent(in) :: predicted, expected
21 !! Predicted and expected values
22 real(real32), dimension(size(predicted,2)) :: output
23 !! Accuracy of the model
24 end function compute_accuracy_function
25 end interface
26
27 contains
28
29 !###############################################################################
30 pure function categorical_score(predicted, expected) result(output)
31 !! Compute the categorical accuracy of a model
32 !!
33 !! This function is only valid for categorical/classification datasets
34 implicit none
35
36 !! Arguments
37 real(real32), dimension(:,:), intent(in) :: predicted, expected
38 !! Predicted and expected values
39 real(real32), dimension(size(expected,2)) :: output
40 !! Categorical accuracy
41
42 ! Local variables
43 integer :: s
44 !! Loop index
45
46 !! Compute the accuracy
47 do concurrent(s=1:size(expected,2))
48 if (maxloc(expected(:,s),dim=1).eq.maxloc(predicted(:,s),dim=1)) then
49 output(s) = 1._real32
50 else
51 output(s) = 0._real32
52 end if
53 end do
54
55 end function categorical_score
56 !###############################################################################
57
58
59 !###############################################################################
60 pure function mae_score(predicted, expected) result(output)
61 !! Compute the mean absolute error of a model
62 !!
63 !! This function is only valid for continuous datasets
64 implicit none
65
66 ! Arguments
67 real(real32), dimension(:,:), intent(in) :: predicted, expected
68 !! Predicted and expected values
69 real(real32), dimension(size(expected,2)) :: output
70 !! Mean absolute error
71
72 ! Compute the accuracy
73 output = 1._real32 - sum(abs(expected - predicted),dim=1)/size(expected,1)
74
75 end function mae_score
76 !###############################################################################
77
78
79 !###############################################################################
80 pure function mse_score(predicted, expected) result(output)
81 !! Compute the mean squared error of a model
82 !!
83 !! This function is only valid for continuous datasets
84 implicit none
85
86 ! Arguments
87 real(real32), dimension(:,:), intent(in) :: predicted, expected
88 !! Predicted and expected values
89 real(real32), dimension(size(expected,2)) :: output
90 !! Mean squared error
91
92 ! Compute the accuracy
93 output = 1._real32 - &
94 sum((expected - predicted)**2._real32,dim=1)/size(expected,1)
95
96 end function mse_score
97 !###############################################################################
98
99
100 !###############################################################################
101 pure function rmse_score(predicted, expected) result(output)
102 !! Compute the root mean squared error of a model
103 !!
104 !! This function is only valid for continuous datasets
105 implicit none
106
107 ! Arguments
108 real(real32), dimension(:,:), intent(in) :: predicted, expected
109 !! Predicted and expected values
110 real(real32), dimension(size(expected,2)) :: output
111 !! Root mean squared error
112
113 ! Compute the accuracy
114 output = 1._real32 - &
115 sqrt(sum((expected - predicted)**2._real32,dim=1)/size(expected,1))
116
117 end function rmse_score
118 !###############################################################################
119
120
121 !###############################################################################
122 pure function r2_score(predicted, expected) result(output)
123 !! Compute the R^2 score of a model
124 !!
125 !! This function is only valid for continuous datasets
126 implicit none
127
128 ! Arguments
129 real(real32), dimension(:,:), intent(in) :: predicted, expected
130 real(real32), dimension(size(expected,2)) :: y_mean, rss, tss
131 real(real32), dimension(size(expected,2)) :: output
132
133 ! Local variables
134 real(real32), parameter :: epsilon = 1.E-8_real32
135 !! Small value to avoid division by zero
136 integer :: s
137 !! Loop index
138
139 do s = 1, size(expected,2)
140 ! compute mean of true/expected
141 y_mean(s) = sum(expected(:,s),dim=1) / size(expected,dim=1)
142
143 ! compute total sum of squares
144 tss(s) = sum( ( expected(:,s) - y_mean(s) ) ** 2._real32, dim=1 )
145
146 ! compute residual sum of squares
147 rss(s) = sum( ( expected(:,s) - predicted(:,s) ) ** 2._real32, dim=1 )
148
149 ! compute accuracy (R^2 score)
150 if(abs(rss(s)).lt.epsilon)then
151 output(s) = 1._real32
152 elseif(abs(tss(s)).lt.epsilon.or.rss(s)/tss(s).gt.1._real32)then
153 output(s) = 0._real32
154 else
155 output(s) = 1._real32 - rss(s)/tss(s)
156 end if
157 end do
158
159 end function r2_score
160 !###############################################################################
161
162 end module athena__accuracy
163