Skip to content

Commit

Permalink
add code analyzer
Browse files Browse the repository at this point in the history
  • Loading branch information
ivokwee committed Mar 20, 2023
1 parent fc8a0dd commit 0aa240a
Show file tree
Hide file tree
Showing 5 changed files with 159 additions and 2 deletions.
148 changes: 148 additions & 0 deletions tools/utils/code-analyzer.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,148 @@
##
## This file is part of the Omics Playground project.
## Copyright (c) 2018-2023 BigOmics Analytics SA. All rights reserved.
##


setwd("~/Playground/omicsplayground")
rfiles <- dir("components", recursive=TRUE, patter=".*[.][rR]$",full.names=TRUE)

## scan all function declarations
func.declared <- c()
f <- rfiles[1]
for(f in rfiles) {
src <- readLines(f)
## detect allw function declaration
here.func <- grep("=[ ]*function|<-[ ]*function",src)
these.func <- trimws(sub("<-.*|=.*","",src[here.func]))
these.func <- gsub(".*[ ]|#","",these.func)
if(length(these.func)) {
ff <- cbind(these.func, f)
func.declared <- rbind( func.declared, ff)
}
}
colnames(func.declared) <- c("function.name","file")

## create regexpression for all functions
all.func <- func.declared[,"function"]
func.rexp <- paste0("[\\^ =-\\(]",all.func,"[\\(@,]") ## NEED RETHINK
names(func.rexp) <- all.func

## detect which functions are used in each file
func.used <- c()
f <- rfiles[10]
for(f in rfiles) {
## detect functions used
src <- readLines(f)
using.func <- grep(paste(func.rexp,collapse="|"), src)
using.func
if(length(using.func)==0) next
n=using.func[1]
func.calls <- c()
for(n in using.func){
s <- src[n]
f1 <- names(which(sapply(func.rexp, function(f) grepl(f,s))))
func.calls <- c(func.calls, f1)
}
if(length(func.calls)>0) {
tt <- table(func.calls)
rr <- data.frame(f, "function.called"=names(tt), "nfreq"=as.integer(tt))
func.used <- rbind(func.used, rr)
}
}
colnames(func.used) <- c("file","function.name","nfreq")

head(func.declared,20)
head(func.used,20)

## detect multiple declared functions
ndeclared <- table(func.declared[,"function.name"])
multiple.declared <- names(which(ndeclared > 1))
ww <- tapply( func.declared[,"file"], func.declared[,"function.name"],
function(w) paste(gsub(".*/","",sort(unique(w))),collapse=', '))
df1 <- data.frame( 'function.name'=names(ndeclared), n.declared=as.integer(ndeclared), where.declared=ww)
head(df1)
head(df1[which(df1$n.declared>1),],20)

## detect not used functions
head(func.declared,20)
head(func.used,20)

nused <- table(func.used[,"function.name"])
uu <- tapply( func.used[,"file"], func.used[,"function.name"],
function(w) paste(gsub(".*/","",sort(unique(w))),collapse=', '))
df2 <- data.frame( 'function.name'=names(nused), n.used=as.integer(nused), where.used=uu)
head(df2)

df2 <- df2[match(df1$function.name, df2$function.name),]
df2$n.used[is.na(df2$n.used)] <- 0
df2$function.name <- NULL
df <- cbind(df1, df2)
rownames(df) <- NULL

df <- df[,c("function.name","n.declared","n.used","where.declared","where.used")]

## write.csv(df, file="code-analyzer-output.csv")


## -----------------------------------------------------------------------------
## -----------------------------------------------------------------------------
## -----------------------------------------------------------------------------

library(shiny)
library(DT)

ui = fluidPage(
h2("Code analytics: function declaration and calls"),
div( class="row",
actionButton("show_all","all"),
actionButton("show_multi","multiple-declared"),
actionButton("show_notused","not used")
),
DT::DTOutput("dt")
)

server = function(input, output, session) {

filtered_df <- reactiveVal(df)

observeEvent( input$show_all, {
filtered_df( df )
})

observeEvent( input$show_notused, {
df1 <- df[ df$n.used==0,]
df1 <- df1[order(-df1$n.declared),]
filtered_df( df1)
})

observeEvent( input$show_multi, {
df1 <- df[ df$n.declared > 1,]
df1 <- df1[order(-df1$n.declared),]
filtered_df(df1)
})

output$dt <- DT::renderDT(
DT::datatable( filtered_df(),
extensions = 'Scroller',
options = list(
deferRender = FALSE,
dom = 't',
##columnDefs = list(list(className = 'dt-center', targets = 5)),
scrollY = 800,
scroller = TRUE,
scrollX = TRUE,
pageLength = 80)
) %>%
formatStyle(
'n.declared',
backgroundColor = styleInterval(1, c('white', 'yellow'))
) %>%
formatStyle(
'n.used',
backgroundColor = styleInterval(0, c('salmon', 'white'))
)
)
}

shiny::shinyApp(ui, server=server, options=list(launch.browser=TRUE))
4 changes: 4 additions & 0 deletions tools/utils/init-pgxfolder.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
##
## This file is part of the Omics Playground project.
## Copyright (c) 2018-2023 BigOmics Analytics SA. All rights reserved.
##

RDIR="../R"
FILES="../lib"
Expand Down
2 changes: 1 addition & 1 deletion tools/utils/testBoard.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
##
## This file is part of the Omics Playground project.
## Copyright (c) 2018-2021 BigOmics Analytics Sagl. All rights reserved.
## Copyright (c) 2018-2023 BigOmics Analytics SA. All rights reserved.
##

library(shiny)
Expand Down
2 changes: 1 addition & 1 deletion tools/utils/testPlotModule.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
##
## This file is part of the Omics Playground project.
## Copyright (c) 2018-2021 BigOmics Analytics Sagl. All rights reserved.
## Copyright (c) 2018-2023 BigOmics Analytics SA. All rights reserved.
##

if(interactive()) {
Expand Down
5 changes: 5 additions & 0 deletions tools/utils/update-pgxfolder.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
##
## This file is part of the Omics Playground project.
## Copyright (c) 2018-2023 BigOmics Analytics SA. All rights reserved.
##

RDIR = "../R"
FILES = "../lib"
FILESX = "../libx"
Expand Down

0 comments on commit 0aa240a

Please sign in to comment.