R/RCodeParsing.R

Defines functions readFileAsString splitStringByLines jointCharToLine .grepl isFunDeclaration removeSpaces isAssignment addBlockLevelColumn

# ---------------------------------------------------------------
#
#    Author     : Damian Skrzypiec <damian.j.skrzypiec@gmail.com>
#
#    Date       : 2018-01-01 01:44:40
#
#    Description: Functions for parsing single R Script.
#
# ---------------------------------------------------------------




readFileAsString <- function(path)
{
    isValidPath(path)
    is.Rfile(getLastEleOfPath(path))

    return(readChar(path, file.info(path)$size))
}


splitStringByLines <- function(rawString)
{
    isCharacter(rawString)
    result <- character(0)

    if (isWindowsOS()) {
        result <- strsplit(x = rawString, split = "\r\n", fixed = TRUE)[[1]]
    }

    if (isLinuxOS()) {
        result <- strsplit(x = rawString, split = "\n", fixed = TRUE)[[1]]
    }

    # TODO: case for iOS
    return(result)
}


jointCharToLine <- function(chars)
{
    isSingleCharacters(chars)
    return(paste0(chars, collapse = ""))
}


.grepl <- function(pattern, x, ...)
{
    isCharacter(pattern)
    isCharacter(x)
    return(grepl(pattern, x, ...))
}


isFunDeclaration <- function(codeLine)
{
    pattern <- "^[^#]*(|<-|=)(|[[:space:]]+)function(|[[:space:]]+)\\(*\\)*\\{*(\\})*"
    return(.grepl(pattern, codeLine, fixed = FALSE))
}


removeSpaces <- function(codeLine)
{
    isCharacter(codeLine)
    splitBySpace <- strsplit(x = codeLine, split = "[[:space:]]", fixed = FALSE)[[1]]
    return(splitBySpace[sapply(splitBySpace, nchar) > 0])
}


isAssignment <- function(phrase)
{
    isCharacter(phrase)
    return(phrase == "<-" | phrase == "=")
}


addBlockLevelColumn <- function(rScriptChar)
{
	isRScriptChars(rScriptChar)
	nCharInScript <- nrow(rScriptChar$Data)
	blockLevels <- integer(nCharInScript)
	charsInScript <- rScriptChar$Data$Char
	numLine <- rScriptChar$Data$LineId
	isInsideComment <- FALSE

	for (charId in seq_len(nCharInScript))
	{
		currChar <- charsInScript[charId]
		if (isInsideComment | currChar == "#") {
			isInsideComment <- TRUE
		}

		if (charId == 1) {
			next
		}

		if (currChar != "#" & numLine[charId - 1] != numLine[charId]) { 		# new line resets comment
			isInsideComment <- FALSE
		}

		if (!isInsideComment &  currChar == "{") {
			if (charId == 1) {
				blockLevels[charId] <- 1
			} else {
				blockLevels[charId] <- blockLevels[charId - 1] + 1
			}
		}

		if (!isInsideComment &  currChar == "}") {
			if (charId > 1)	{
				blockLevels[charId] <- blockLevels[charId - 1] - 1
			}
		}
	}

	rScriptChar$Data$BlockLvl <- cumsum(blockLevels)
	return(rScriptChar)
}
DSkrzypiec/oRtrack documentation built on May 23, 2019, 7:32 a.m.