blob: 94c3572d2df40d9fb7c6630276c6255ab1a6c032 [file] [log] [blame]
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -08001# Copyright 2018 Open Networking Foundation (ONF)
Jeremy Ronquillo908cb442017-12-07 08:58:09 -08002#
3# Please refer questions to either the onos test mailing list at <onos-test@onosproject.org>,
4# the System Testing Plans and Results wiki page at <https://wiki.onosproject.org/x/voMg>,
5# or the System Testing Guide page at <https://wiki.onosproject.org/x/WYQg>
6#
7# TestON is free software: you can redistribute it and/or modify
8# it under the terms of the GNU General Public License as published by
9# the Free Software Foundation, either version 2 of the License, or
10# (at your option) any later version.
11#
12# TestON is distributed in the hope that it will be useful,
13# but WITHOUT ANY WARRANTY; without even the implied warranty of
14# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15# GNU General Public License for more details.
16#
17# You should have received a copy of the GNU General Public License
18# along with TestON. If not, see <http://www.gnu.org/licenses/>.
19#
20# If you have any questions, or if you don't understand R,
21# please contact Jeremy Ronquillo: j_ronquillo@u.pacific.edu
22
23# **********************************************************
24# STEP 1: Data management.
25# **********************************************************
26
27print( "**********************************************************" )
28print( "STEP 1: Data management." )
29print( "**********************************************************" )
30
31# Command line arguments are read. Args include the database credentials, test name, branch name, and the directory to output files.
32print( "Reading commmand-line args." )
33args <- commandArgs( trailingOnly=TRUE )
34
35databaseHost <- 1
36databasePort <- 2
37databaseUserID <- 3
38databasePassword <- 4
39testSuiteName <- 5
40branchName <- 6
41testsToInclude <- 7
42buildToShow <- 8
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -080043saveDirectory <- 9
Jeremy Ronquillo908cb442017-12-07 08:58:09 -080044
45# ----------------
46# Import Libraries
47# ----------------
48
49print( "Importing libraries." )
50library( ggplot2 )
51library( reshape2 )
52library( RPostgreSQL )
53
54# -------------------
55# Check CLI Arguments
56# -------------------
57
58print( "Verifying CLI args." )
59
60if ( is.na( args[ saveDirectory ] ) ){
61
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -080062 print( paste( "Usage: Rscript testCategoryBuildStats.R",
Jeremy Ronquillo908cb442017-12-07 08:58:09 -080063 "<database-host>",
64 "<database-port>",
65 "<database-user-id>",
66 "<database-password>",
67 "<test-suite-name>",
68 "<branch-name>",
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -080069 "<tests-to-include-(as-one-string-sep-groups-by-semicolon-title-as-first-group-item-sep-by-dash)>",
Jeremy Ronquillo908cb442017-12-07 08:58:09 -080070 "<build-to-show>",
Jeremy Ronquillo908cb442017-12-07 08:58:09 -080071 "<directory-to-save-graphs>",
72 sep=" " ) )
73
74 quit( status = 1 ) # basically exit(), but in R
75}
76
77# ------------------
78# SQL Initialization
79# ------------------
80
81print( "Initializing SQL" )
82
83con <- dbConnect( dbDriver( "PostgreSQL" ),
84 dbname = "onostest",
85 host = args[ databaseHost ],
86 port = strtoi( args[ databasePort ] ),
87 user = args[ databaseUserID ],
88 password = args[ databasePassword ] )
89
90# ---------------------
91# Test Case SQL Command
92# ---------------------
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -080093
Jeremy Ronquillo908cb442017-12-07 08:58:09 -080094print( "Generating Test Case SQL command." )
95
96tests <- "'"
97for ( test in as.list( strsplit( args[ testsToInclude ], "," )[[1]] ) ){
98 tests <- paste( tests, test, "','", sep="" )
99}
100tests <- substr( tests, 0, nchar( tests ) - 2 )
101
102fileBuildToShow <- args[ buildToShow ]
103operator <- "= "
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800104buildTitle <- ""
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800105if ( args[ buildToShow ] == "latest" ){
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800106 buildTitle <- "\nLatest Test Results"
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800107 operator <- ">= "
108 args[ buildToShow ] <- "1000"
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800109} else {
110 buildTitle <- paste( " \n Build #", args[ buildToShow ] , sep="" )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800111}
112
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800113tests <- strsplit( args[ testsToInclude ], ";" )
114dbResults <- list()
115titles <- list()
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800116
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800117for ( i in 1:length( tests[[1]] ) ){
118 splitTestList <- strsplit( tests[[1]][ i ], "-" )
119 testList <- splitTestList[[1]][2]
120 titles[[i]] <- splitTestList[[1]][1]
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800121
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800122 testsCommand <- "'"
123 for ( test in as.list( strsplit( testList, "," )[[1]] ) ){
124 testsCommand <- paste( testsCommand, test, "','", sep="" )
125 }
126 testsCommand <- substr( testsCommand, 0, nchar( testsCommand ) - 2 )
127
128 command <- paste( "SELECT * ",
129 "FROM executed_test_tests a ",
130 "WHERE ( SELECT COUNT( * ) FROM executed_test_tests b ",
131 "WHERE b.branch='",
132 args[ branchName ],
133 "' AND b.actual_test_name IN (",
134 testsCommand,
135 ") AND a.actual_test_name = b.actual_test_name AND a.date <= b.date AND b.build ", operator,
136 args[ buildToShow ],
137 " ) = ",
138 1,
139 " AND a.branch='",
140 args[ branchName ],
141 "' AND a.actual_test_name IN (",
142 testsCommand,
143 ") AND a.build ", operator,
144 args[ buildToShow ],
145 " ORDER BY a.actual_test_name DESC, a.date DESC",
146 sep="")
147 print( "Sending SQL command:" )
148 print( command )
149 dbResults[[i]] <- dbGetQuery( con, command )
150}
151
152print( "dbResult:" )
153print( dbResults )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800154
155# -------------------------------
156# Create Title and Graph Filename
157# -------------------------------
158
159print( "Creating title of graph." )
160
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800161titlePrefix <- paste( args[ testSuiteName ], " ", sep="" )
162if ( args[ testSuiteName ] == "ALL" ){
163 titlePrefix <- ""
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800164}
165
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800166title <- paste( titlePrefix,
167 "Summary of Test Suites - ",
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800168 args[ branchName ],
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800169 buildTitle,
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800170 sep="" )
171
172print( "Creating graph filename." )
173
174outputFile <- paste( args[ saveDirectory ],
175 args[ testSuiteName ],
176 "_",
177 args[ branchName ],
178 "_build-",
179 fileBuildToShow,
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800180 "_test-suite-summary.jpg",
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800181 sep="" )
182
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800183# **********************************************************
184# STEP 2: Organize data.
185# **********************************************************
186
187print( "**********************************************************" )
188print( "STEP 2: Organize Data." )
189print( "**********************************************************" )
190
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800191passNum <- list()
192failNum <- list()
193exeNum <- list()
194skipNum <- list()
195totalNum <- list()
196
197passPercent <- list()
198failPercent <- list()
199exePercent <- list()
200nonExePercent <- list()
201
202actualPassPercent <- list()
203actualFailPercent <- list()
204
205appName <- c()
206afpName <- c()
207nepName <- c()
208
209tmpPos <- c()
210tmpCases <- c()
211
212for ( i in 1:length( dbResults ) ){
213 t <- dbResults[[i]]
214
215 passNum[[i]] <- sum( t$num_passed )
216 failNum[[i]] <- sum( t$num_failed )
217 exeNum[[i]] <- passNum[[i]] + failNum[[i]]
218 totalNum[[i]] <- sum( t$num_planned )
219 skipNum[[i]] <- totalNum[[i]] - exeNum[[i]]
220
221 passPercent[[i]] <- passNum[[i]] / exeNum[[i]]
222 failPercent[[i]] <- failNum[[i]] / exeNum[[i]]
223 exePercent[[i]] <- exeNum[[i]] / totalNum[[i]]
224 nonExePercent[[i]] <- ( 1 - exePercent[[i]] ) * 100
225
226 actualPassPercent[[i]] <- passPercent[[i]] * exePercent[[i]] * 100
227 actualFailPercent[[i]] <- failPercent[[i]] * exePercent[[i]] * 100
228
229 appName <- c( appName, "Passed" )
230 afpName <- c( afpName, "Failed" )
231 nepName <- c( nepName, "Skipped/Unexecuted" )
232
233 tmpPos <- c( tmpPos, 100 - ( nonExePercent[[i]] / 2 ), actualPassPercent[[i]] + actualFailPercent[[i]] - ( actualFailPercent[[i]] / 2 ), actualPassPercent[[i]] - ( actualPassPercent[[i]] / 2 ) )
234 tmpCases <- c( tmpCases, skipNum[[i]], failNum[[i]], passNum[[i]] )
235}
236
237relativePosLength <- length( dbResults ) * 3
238
239relativePos <- c()
240relativeCases <- c()
241
242for ( i in 1:3 ){
243 relativePos <- c( relativePos, tmpPos[ seq( i, relativePosLength, 3 ) ] )
244 relativeCases <- c( relativeCases, tmpCases[ seq( i, relativePosLength, 3 ) ] )
245}
246names( actualPassPercent ) <- appName
247names( actualFailPercent ) <- afpName
248names( nonExePercent ) <- nepName
249
250labels <- paste( titles, "\n", totalNum, " Test Cases", sep="" )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800251
252# --------------------
253# Construct Data Frame
254# --------------------
255
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800256print( "Constructing Data Frame" )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800257
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800258dataFrame <- melt( c( nonExePercent, actualFailPercent, actualPassPercent ) )
259dataFrame$title <- seq( 1, length( dbResults ), by = 1 )
260colnames( dataFrame ) <- c( "perc", "key", "suite" )
261
262dataFrame$xtitles <- labels
263dataFrame$relativePos <- relativePos
264dataFrame$relativeCases <- relativeCases
265dataFrame$valueDisplay <- c( paste( round( dataFrame$perc, digits = 2 ), "% - ", relativeCases, " Tests", sep="" ) )
266
267dataFrame$key <- factor( dataFrame$key, levels=unique( dataFrame$key ) )
268
269dataFrame$willDisplayValue <- dataFrame$perc > 15.0 / length( dbResults )
270
271for ( i in 1:nrow( dataFrame ) ){
272 if ( relativeCases[[i]] == "1" ){
273 dataFrame[ i, "valueDisplay" ] <- c( paste( round( dataFrame$perc[[i]], digits = 2 ), "% - ", relativeCases[[i]], " Test", sep="" ) )
274 }
275 if ( !dataFrame[ i, "willDisplayValue" ] ){
276 dataFrame[ i, "valueDisplay" ] <- ""
277 }
278}
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800279
280print( "Data Frame Results:" )
281print( dataFrame )
282
283# **********************************************************
284# STEP 3: Generate graphs.
285# **********************************************************
286
287print( "**********************************************************" )
288print( "STEP 3: Generate Graph." )
289print( "**********************************************************" )
290
291# -------------------
292# Main Plot Generated
293# -------------------
294
295print( "Creating main plot." )
296# Create the primary plot here.
297# ggplot contains the following arguments:
298# - data: the data frame that the graph will be based off of
299# - aes: the asthetics of the graph which require:
300# - x: x-axis values (usually iterative, but it will become build # later)
301# - y: y-axis values (usually tests)
302# - color: the category of the colored lines (usually status of test)
303
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800304# -------------------
305# Main Plot Formatted
306# -------------------
307
308print( "Formatting main plot." )
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800309mainPlot <- ggplot( data = dataFrame, aes( x = suite,
310 y = perc,
311 fill = key ) )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800312
313# ------------------------------
314# Fundamental Variables Assigned
315# ------------------------------
316
317print( "Generating fundamental graph data." )
318
319theme_set( theme_grey( base_size = 26 ) ) # set the default text size of the graph.
320
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800321xScaleConfig <- scale_x_continuous( breaks = dataFrame$suite,
322 label = dataFrame$xtitles )
323yScaleConfig <- scale_y_continuous( breaks = seq( 0, 100,
324 by = 10 ) )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800325
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800326xLabel <- xlab( "" )
327yLabel <- ylab( "Total Test Cases (%)" )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800328
329imageWidth <- 15
330imageHeight <- 10
331imageDPI <- 200
332
333# Set other graph configurations here.
334theme <- theme( plot.title = element_text( hjust = 0.5, size = 32, face ='bold' ),
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800335 axis.text.x = element_text( angle = 0, size = 25 - 1.25 * length( dbResults ) ),
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800336 legend.position = "bottom",
337 legend.text = element_text( size = 22 ),
338 legend.title = element_blank(),
Jeremy Ronquillo94f99dd2018-01-05 11:11:27 -0800339 legend.key.size = unit( 1.5, 'lines' ),
340 plot.subtitle = element_text( size=16, hjust=1.0 ) )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800341
Jeremy Ronquillo94f99dd2018-01-05 11:11:27 -0800342subtitle <- paste( "Last Updated: ", format( Sys.time(), format = "%b %d, %Y at %I:%M %p %Z" ), sep="" )
343
344title <- labs( title = title, subtitle = subtitle )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800345
346# Store plot configurations as 1 variable
347fundamentalGraphData <- mainPlot +
348 xScaleConfig +
349 yScaleConfig +
350 xLabel +
351 yLabel +
352 theme +
353 title
354
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800355# ---------------------------
356# Generating Bar Graph Format
357# ---------------------------
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800358
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800359print( "Generating bar graph." )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800360
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800361unexecutedColor <- "#CCCCCC" # Gray
362failedColor <- "#E02020" # Red
363passedColor <- "#16B645" # Green
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800364
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800365colors <- scale_fill_manual( values=c( if ( "Skipped/Unexecuted" %in% dataFrame$key ){ unexecutedColor },
366 if ( "Failed" %in% dataFrame$key ){ failedColor },
367 if ( "Passed" %in% dataFrame$key ){ passedColor } ) )
368
369barGraphFormat <- geom_bar( stat = "identity", width = 0.8 )
370
371barGraphValues <- geom_text( aes( x = dataFrame$suite,
372 y = dataFrame$relativePos,
373 label = format( paste( dataFrame$valueDisplay ) ) ),
374 size = 15.50 / length( dbResults ) + 2.33, fontface = "bold" )
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800375
376result <- fundamentalGraphData +
Jeremy Ronquillo478a8c12018-01-08 13:59:47 -0800377 colors +
378 barGraphFormat +
379 barGraphValues
Jeremy Ronquillo908cb442017-12-07 08:58:09 -0800380
381# -----------------------
382# Exporting Graph to File
383# -----------------------
384
385print( paste( "Saving result graph to", outputFile ) )
386
387tryCatch( ggsave( outputFile,
388 width = imageWidth,
389 height = imageHeight,
390 dpi = imageDPI ),
391 error = function( e ){
392 print( "[ERROR] There was a problem saving the graph due to a graph formatting exception. Error dump:" )
393 print( e )
394 quit( status = 1 )
395 }
396 )
397
398print( paste( "[SUCCESS] Successfully wrote result graph out to", outputFile ) )
399quit( status = 0 )