From 29fef4fc21cf38e3da4050dfc293d728651b478c Mon Sep 17 00:00:00 2001 From: "G. Grothendieck" Date: Sun, 8 Oct 2006 00:00:00 +0000 Subject: [PATCH] version 0.2-1 --- DESCRIPTION | 6 +-- R/fn.R | 50 ++++++++++++++----- demo/00Index | 5 +- demo/gsubfn-chron.R | 22 ++++++++ demo/gsubfn-gries.R | 29 +++++++++++ demo/gsubfn-si.R | 11 ++++ inst/1 | 20 -------- inst/NEWS | 24 ++++++++- inst/THANKS | 6 +++ inst/sample.txt | 100 +++++++++++++++++++++++++++++++++++++ man/as.function.formula.Rd | 13 +++-- man/cati.Rd | 2 +- man/fn.Rd | 21 ++++---- man/gsubfn-package.Rd | 51 +++++++++++++------ man/gsubfn.Rd | 39 ++++++--------- man/strapply.Rd | 11 +++- 16 files changed, 317 insertions(+), 93 deletions(-) create mode 100755 demo/gsubfn-chron.R create mode 100755 demo/gsubfn-gries.R create mode 100755 demo/gsubfn-si.R delete mode 100755 inst/1 create mode 100755 inst/THANKS create mode 100755 inst/sample.txt diff --git a/DESCRIPTION b/DESCRIPTION index 9f0a289..7e8f6a2 100755 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: gsubfn -Version: 0.2-0 -Date: 2006-10-05 +Version: 0.2-1 +Date: 2006-10-08 Title: Miscellaneous utilities for strings and function arguments. Author: G. Grothendieck Maintainer: G. Grothendieck @@ -16,4 +16,4 @@ Description: gsubfn is like gsub but can take a replacement function Depends: R (>= 2.0.0) License: GPL (Version 2 or later) URL: http://code.google.com/p/gsubfn/ -Packaged: Thu Oct 5 20:22:59 2006; Kates +Packaged: Mon Oct 9 23:13:03 2006; Kates diff --git a/R/fn.R b/R/fn.R index eed4ca4..685be4d 100755 --- a/R/fn.R +++ b/R/fn.R @@ -1,6 +1,6 @@ as.function.formula <- function(x, ...) { - vars <- all.vars(x[[2]]) + vars <- setdiff(all.vars(x[[2]]), c("letters", "LETTERS", "pi")) if (length(vars) == 0) { f <- function() {} } else { @@ -29,26 +29,48 @@ fn <- structure(NA, class = "fn") mc1 <- mc[-1] nm <- names(mc1) if (is.null(nm)) nm <- rep("", length(args)) - idx <- match("simplify", tolower(nm), nomatch = 0) + + mcList <- as.list(mc1) + p <- parent.frame() + mcListE <- lapply(mcList, eval, p) + + # if simplify found set it and remove it from lists simplify <- NULL + idx <- match("simplify", tolower(nm), nomatch = 0) if (idx > 0) { - if (!is.logical(args[[idx]])) { - simplify <- args[[idx]] - args <- args[-idx] + if (!is.logical(mcListE[[idx]])) { + simplify <- mcListE[[idx]] + mcListE <- mcListE[-idx] + mcList <- mcList[-idx] nm <- nm[-idx] } } - is.fo <- sapply(args, function(x) is(x, "formula")) - num.fo <- sum(is.fo) - is.funfo <- is.fo & (num.fo == 1 | seq(along = args) > 1 | + # arg1.idx is the location of argument 1 in mcList + # is.fo is a logical vector indicating whether + # each list element is or is not a formula + # is.funfo is true for formulas to be translated + + + is.fo <- sapply(mcListE, function(x) is(x, "formula")) + arg1.idx <- 0 + if (is(args[[1]], "formula")) + for(i in seq(along = mcListE)) + if (is.fo[i] && format(mcList[[i]]) == format(args[[1]])) + arg1.idx <- i + num.fo <- sum(is.fo) + is.funfo <- is.fo & (num.fo == 1 | + seq(along = mcList) != arg1.idx | nm == "FUN") - mcList <- as.list(mc)[-1] - if (idx > 0) mcList <- mcList[-idx] - for(i in seq(along = args)) { - if (is.fo[i] && (num.fo == 1 || i > 1 || nm[[i]] == "FUN")) - mcList[[i]] <- as.function(args[[i]]) + #for(i in seq(along = args)) { + # if (is.fo[i] && (num.fo == 1 || i > 1 || nm[[i]] == "FUN")) + # mcList[[i]] <- as.function(args[[i]]) + for(i in seq(along = mcList)) { + if (is.funfo[i]) { + # mcList[[i]] <- as.function(args[[i]]) + mcList[[i]] <- as.function(mcListE[[i]]) + } } # out <- do.call(FUN, args) out <- do.call(FUN, mcList, env = parent.frame()) @@ -64,3 +86,5 @@ fn <- structure(NA, class = "fn") # fn$list(x ~ 2*x) # fn$mapply(~ x + y, 1:10, 21:30) + + diff --git a/demo/00Index b/demo/00Index index 472f3e6..22203a4 100755 --- a/demo/00Index +++ b/demo/00Index @@ -1 +1,4 @@ -gsubfn-cut Use strapply to extract endpoints from cut labels +gsubfn-chron read in zoo data with chron datetimes. +gsubfn-gries Stefan Gries' Linguistics code. +gsubfn-cut Use strapply to extract endpoints from cut labels. +gsubfn-si Replace SI scale letter with number, diff --git a/demo/gsubfn-chron.R b/demo/gsubfn-chron.R new file mode 100755 index 0000000..cb90e11 --- /dev/null +++ b/demo/gsubfn-chron.R @@ -0,0 +1,22 @@ + +# Use read.zoo to read data with a chron time index +# Ignore fractional seconds. + +library(zoo) +library(chron) +library(gsubfn) + +# test data +Lines <- "2006-01-24 02:41:24.00011,1.22930000,5,1.22950000,7 +2006-01-25 04:41:24.00011,1.22930000,5,1.22950000,7 +2006-01-26 07:41:24.00011,1.22930000,5,1.22950000,7" + +# convert to chron +to.chron <- function(x) + strapply(format(x), "([0-9-]+) ([0-9:]+)", + ~ chron(as.Date(dd), tt), backref = -2,simplify = c) + +con <- textConnection(Lines) +read.zoo(con, sep = ",", FUN = to.chron) +close(con) + diff --git a/demo/gsubfn-gries.R b/demo/gsubfn-gries.R new file mode 100755 index 0000000..efefc4c --- /dev/null +++ b/demo/gsubfn-gries.R @@ -0,0 +1,29 @@ + +# linguistic applications by Stefan Th. Gries + +# create word frequency list from the gsubfn COPYING file + +fn1 <- system.file("COPYING", package = "gsubfn") +Lines1 <- tolower(scan(fn1, what = "char", sep = "\n")) +tail(sort(table(unlist(strapply(Lines1, "\\w+", perl = TRUE))))) + +# frequency list of words from an SGML-annotated text file +# sampled from the British National Corpus" + +fn2 <- system.file("sample.txt", package = "gsubfn") +Lines2 <- scan(fn2, what = "char", sep = "\n") +tagged.corpus.sentences <- grep("^([^<]*)", backref = -1)) +words <- gsub(" $", "", words) +tail(words, 25) + +# frequency list of words AND tags from same file + +word.tag.pairs <- unlist(strapply(tagged.corpus.sentences, "<[^<]*")) +cleaned.word.tag.pairs <- grep("Right +It is virtually impossible for a hearing person to imagine what it is like to be born into silence. +The brief contains schedules and an organisational chart. +Joyce +&bquo;He's just a few minutes early for the unveiling of the new me. +She had turned as he entered, as if some mystical outside force had willed it. +Oh sorry apologize to the last guy he didn't. +Also, the project is proving to be even larger than originally thought. +One more child had died in 1768, shortly to be followed by the births of daughters Elizabeth and Mary. +As for NT, Microsoft is back describing it as primarily a server operating system, and acknowledging that vendors are unlikely to bundle it with more than about 10% of the desktop machines they ship. +It now also has multiple SCSI-2 channel support so that the system can link to a wider variety of disk, tape and other input-output devices. +The signals fluctuate in cycles: if radio energy fluctuates at one cycle every second, then it has a frequency of one Hertz. +In implementing our strategy, we aim to: +To say I've had it, yeah. +Those are my only remaining memories of the first five years. +Tickled pink… +Amid the celebrations of Sunderland becoming the United Kingdom's newest city, there was much talk of new investment and jobs following in the wake of the announcement. +YOU CAN'T CATCH HIV IN ANY OF THESE WAYS: +DOUBLE TAKE +Aye. +Amand v. Home Secretary and Minister of Defence of Royal Netherlands Government [1943] A.C. 147, H.L. (E.); Carr v. Atkins [1987] Q.B. +If one plots the sites of all the recently-active volcanoes in the world on a map, one finds that several distinct, narrow chains exist, some of these running along the edges of continental land masses, some along island arcs and some of them through the sea [see Fig. 1]. +Just off dry, infact. +Now by that he meant that the ends sought should be closely defined and should not change and the means adopted should be effective and they should not change and the consequence is that adversaries then move into er er conflict but the conflict itself is self-limiting in the sense that one side will accept defeat er and, and the consequences of victory and clearly these consequences are not so severe to the state as to jeopardise its existence. +The BBC staff union Bectu called the recommendations a &bquo;secret agenda&equo; by which the BBC hoped to pre-empt public debate about its size and role by &bquo;drastic job cuts&equo; and reducing essential resources. +Dumper trucks will normally not be classified as motor vehicles as they are not intended or adapted for use on roads. +Erm . +The Franks, over whom Charlemagne came to reign in the year 768, were originally a loose confederation of Germanic tribes. +The blaze at Bunchrew Park started when Simon Kent, 25, from Fareham, and Joanne Womar, 23, from Portsmouth, were changing the refill of a gas lamp. +Right simply because we can rewrite this top expression as AQ to the minus beta. +Is it the will of the assembly to accept that addendum? +Are there any major problems with Susan and John at all Tracey? +the organisation of Information Services, with good integration of various elements provided for students and a conscious attempt to offset the continued pressure on library resource. +The pair joined 18 other members of the Royal Auxiliary Air Force Regiment from RAF Honington in Suffolk, to achieve a total descent of 14,400ft the approximate equivalent in height to the Matterhorn mountain in the Alps. +The aim is to reduce the pattern level ambiguity until only allowable words remain. +If you measure a web built outdoors, you will know how large the cage must be. +On March 14 the Lithuanian Supreme Council passed a resolution saying that Lithuanians would no longer be required to serve in the Red Army and that conscripts who deserted would not be held criminally responsible. +WELLA! +Richfield International Land and Investment Co. +We now in manufacturing where there's been a decline in employment since the nineteen sixties, we now have four million workers in manufacturing producing more than seven million produced fifteen years ago. +GONE WEST +Okay? +Was workers control a prominent part of people's thinking on this like? +" Postcript: and so to bed", an unmistakable token of its author's skill and wit, is presented in the form of a short story narrated from two viewpoints, His and Hers, which allude to the style of actionbooks and romances respectively. +Three years later he switched to the Daily Mirror; he was still based in Yorkshire, covering the local beat. +The paper was also highly commended in the UK Press Gazette Regional Newspaper Awards. +The largest previous Semtex bomb on the mainland 70lb did not explode. +TUNISIA: Islam student leader Faisal Barakat, who died in custody in October 1991, was tortured to death, according to an expert analysis of the official autopsy report commissioned by AI from a professor of forensic medicine. +When he started at the NHS in Scotland in 1989 he took the same approach. +They did, do then, put a pencil to there, mm you've already done it haven't it +An orientation now among many of these displaced militants no longer on the working class but on the peasantry and on developing the struggle of the peasantry as a way of creating a base, a new base, er for the Communist Party in the countryside. +But" Jolly Jack" was evidently one thing and" Poor Jack" another. +Arsonists destroy Greek forests +A smaller majority of Labour partisans asserted that their papers had a pro-Labour bias (22 per cent rising to 32 per cent). +The growth has come from privatisation of services provided in the public sectors, particularly healthcare and education and from catering for the public. +For example, the government could create a flow from the private sector by selling government stock. +In so doing he may come as near as he can ever hope to an understanding of war as people of the late Middle Ages knew it, no easy task even in the most favourable conditions, but one which cannot be attempted with any hope of success without a proper appreciation of the many threads which make up history. +Photovoltaics is still five times as expensive as conventional power generation. +In particular, the Anadarko/LASMO/Maersk joint venture is excited about a recent adjacent discovery in the northern Ghadames basin. +For some departments in the University visits can normally only be arranged on certain weekdays (typically Wednesday afternoons), and some faculties have preferred days for visits: Law (Friday afternoons); Medicine (Wednesday afternoons only); Music (Thursday afternoons). +His descendants were to have good reason for echoing such sentiments in relation to the behaviour of Henry VIII's troops in Scotland. +It is an abstract art, which we none the less consume as readers rather than as connoisseurs of pure form. +As an alternative, the investor might consider investing in the CD just considered. +From what I can gather he was as mad as a hatter, and really no good at all. +Thickets of fawn papery stems, tender green as they unfurl in the spring, have a specialized ecology all of their own. +It is applicable to a wide range of patients and their complaints, and its main limitations are in all likelihood the limitations of the practitioner himself. +Ah ah! +Aha. +As Johnson puts it (1975), trust is not a &bquo;one shot agreement&equo; but is continually negotiated during field-work (also see Emerson 1983: 176; van Maanen 1982). +The latter was essentially isolated within the Conservative parliamentary party. +But does that stop the problem if if we report someone for depositing litter I E a settee, I mean they don't want to really deposit it there, is it quality of life that's forced them to do it. +cos our, our +have even put him at two, you know, so that's brilliant! +We usually are. +Inside The Brotherhood (Granada), produced by Claudia Milne and Martin Short, dug into the most notorious area of Masonic influence, local government. +(Boys have been engaged in flower arranging, &bquo;care&equo; activities and theatrical make–up). +One example of how science clearly falls within the remit of another department is in environmental policy. +If you've ever wanted to get your hands on a Leica then a series of three Day Leica School Courses may give you your chance. +In this judgment I shall use the expression &bquo;unregistered company&equo; to mean any company which is liable to be wound up under Part V of the Act of 1986. +Alright chief. +South Shore +Again, according to self reports from people who've actually been abused in this way. +During the party leadership contest much emphasis had been placed in the media on the fact that Major had not had the advantage of a privileged home background or education, that his father had once been a trapeze artist, that his family had lived in a flat in Brixton in South London, and that he had left school at 16 and been unemployed for some time. +Even the Association headquarters was worth less than its mortgage. +knowledge of abortive techniques was widespread in factory districts and spreading due to the interchange of information in the mills, to increase in therapeutic abortions carried out by surgeons, and to the publicity of quacks for their abortifacients. +Crustose lichens . +He accused Labour and the Liberal Democrats of flirting with PR for party political gain. +By the year 2000 it will overtake the USA in terms of production and account for one-fifth of the energy produced in the world. +All appeared to us to be warm, positive, enthusiastic people always praising, rarely criticising. +Having opened up the process of selecting technologies that surround the core System V.4 operating system beyond Unix System Laboratories Inc, Unix International plans to go to the industry at large for three technologies this year, according to president Peter Cunningham. +DRAMATIC STYLING FROM MO AT M & M +Hang on let me show, let me find a bit of bloody paper here, silly bloody arse +But, in both cases, the need for and expense of the stores arises from the nuclear industry's failure to plan ahead for getting rid of its waste. +On this sheet, on page two, we've er, we've performed equation two, right, on the sheet and the second page and it says that there's, there are two alternative ways of testing for structural change using dummy variables. +For from below there sounds the cracking of twigs. + A a a and that i i if that's sort of what you're saying. +The delay was highlighted in New Scientist (16 December 1982, p 707) and later on the television programme Panorama . +The University will award honourary degrees at the graduation ceremonies on 1 and 2 July. +Treasurer Current account £484.53, Investment account £4820.27. +Thus some affected beams which are riddled with holes and appear to be useless, may be found, on investigation, to contain solid heartwood quite adequate to perform their structural roles. diff --git a/man/as.function.formula.Rd b/man/as.function.formula.Rd index e867312..a0d3186 100755 --- a/man/as.function.formula.Rd +++ b/man/as.function.formula.Rd @@ -12,13 +12,18 @@ \item{\dots}{ Currently not used. } } \value{ - A function is returned whose formal arguments are the free - variables in the formula in the order encountered, whose body + A function is returned whose formal arguments are the + variables in the left hand side, whose body is the expression on the right side of the formula and whose - environment is the environment of the formula. + environment is the environment of the formula. If there is + no left hand side the free variables on the right, in the + order encountered are used as the arguments. \code{letters}, + \code{LETTERS} and \code{pi} are ignored and not used as arguments. + If the left hand side is \code{0} then the function is created as + a zero argument function. } \examples{ as.function(~ as.numeric(x) + as.numeric(y)) - +as.function(x + y ~ as.numeric(x) + as.numeric(y)) # same } \keyword{ character } diff --git a/man/cati.Rd b/man/cati.Rd index af3dda3..6553184 100755 --- a/man/cati.Rd +++ b/man/cati.Rd @@ -57,7 +57,7 @@ None (invisible 'NULL'). } \seealso{ Also see \code{\link{gsubfn}}. } \examples{ -cati("pi = \$pi, pi rounded = `round(pi,2)`\\n") +cati("pi = $pi, pi rounded = `round(pi,2)`\\n") # no comma after 3 as newline specified via end= cati(1, 2, 3, sep = ",", end = "\\n") diff --git a/man/fn.Rd b/man/fn.Rd index 37dbf07..75f7876 100755 --- a/man/fn.Rd +++ b/man/fn.Rd @@ -4,7 +4,7 @@ \title{ Transform formula arguments to functions. } \description{ When used in the form \code{fn\$somefunction(...arguments...)} - it converts formulas among the arguments to somefunction to + it converts formulas among the arguments of somefunction to functions using \code{as.function.formula}. It uses a heuristic to decide which formulas to convert. If any of the following are true then that argument is converted from a formula to a @@ -14,7 +14,7 @@ argument list. } \usage{ -"\$.fn"(x, FUN) +"$.fn"(x, FUN) } \arguments{ \item{x}{ \code{fn}.} @@ -25,9 +25,10 @@ } \examples{ - # use of formula to specify a function. - # LHS of formula is needed since we don't want LETTERS in arg list. - fn$lapply(list(1:4, 1:3), x ~ LETTERS[x]) + # use of formula to specify a function. + # Note that LETTERS, letters and pi are automatically excluded from args + fn$lapply(list(1:4, 1:3), ~ LETTERS[x]) + fn$sapply(1:3, ~ sin((n-1):n * pi/180)) # use of simplify = rbind instead of do.call(rbind, by(...)). # args to anonymous function are automatically determined. @@ -51,14 +52,13 @@ # fn$summaryBy(.~Plant,CO2[-(2:3)],FUN=~mean(range(x)), pref='midrange') } - # generalized inner product - # can replace sum(x*y) with any other expression of interest + # generalized matrix product + # can replace sum(x*y) with any other inner product of interest + # this example just performs matrix multiplication of a times b a <- matrix(4:1, 2) b <- matrix(1:4, 2) fn$apply(b, 2, x ~ fn$apply(a, 1, y ~ sum(x*y))) - a %*% b # same - # integration fn$integrate(~1/((x+1)*sqrt(x)), lower = 0, upper = Inf) @@ -94,9 +94,8 @@ fn$boot(rivers, ~ median(x, d), R = 2000) } - # must specify args so that pi is not included in arg list x <- 0:50/50 - matplot(x, fn$outer(x, 1:8, x + k ~ sin(x * k*pi)), type = 'blobcsSh') + matplot(x, fn$outer(x, 1:8, ~ sin(x * k*pi)), type = 'blobcsSh') } diff --git a/man/gsubfn-package.Rd b/man/gsubfn-package.Rd index e7ce19d..3b84639 100755 --- a/man/gsubfn-package.Rd +++ b/man/gsubfn-package.Rd @@ -8,34 +8,39 @@ gsubfn Generalized \code{"'gsub'"} and associated function. } \details{ -\code{"'gsubfn'"} is like \code{"'gsub'"} except -instead of using a replacement string it passes -the matches and backreferences to a function -which transforms them and then replaces the matches -with that. Some applications include -perl-style string interpolation, splitting a string -based on matches rather than delimiters (using -the function \code{"'strapply'"}) and other -string transformation applications. +gsubfn is an R package that has two purposes: (1) it provides a generalization +of \code{gsub} called \code{gsubfn} which uses a replacement function +(rather than a +replacement string) together with a variety of associated functions, such +as \code{strapply} and \code{cati}, which build upon it. +Applications include string +transforms such as parsing strings based +on content rather than delimiters and perl-style string interpolation. +(2) it provides a compact method of passing anonymous +functions by using formula, rather than function, notation. This facilitates +writing streamlined expressions to call functions whose arguments pass +functions. This has application to the use of +apply, lapply, mapply, sapply, tapply, by, +integrate, optim, outer and other functions in the core of R and in addon +packages. The following are sources of information on \code{"gsubfn"}: \tabular{ll}{ News\tab file.show(system.file("NEWS", package = "gsubfn"))\cr Wish List\tab file.show(system.file("WISHLIST", package = "gsubfn"))\cr +Thanks file\tab file.show(system.file("THANKS", package = "gsubfn"))\cr +License\tab file.show(system.file("COPYING", package = "gsubfn"))\cr +Demo\tab demo("gsubfn-chron")\cr Demo\tab demo("gsubfn-cut")\cr +Demo\tab demo("gsubfn-gries")\cr +Demo\tab demo("gsubfn-si")\cr This File\tab package?gsubfn\cr Help files\tab ?gsubfn, ?strapply, ?cati, ?cati0, ?cat0, ?paste0\cr More Help files\tab ?as.function.format, ?match.funfn, ?"\$.fn"\cr Home page\tab http://code.google.com/p/gsubfn/\cr } -Index: -\preformatted{ -gsubfn Pattern Matching and Replacement -cati cat but with gsubfn-style interpolation. -strapply Apply a function over a string or strings. -} } \examples{ @@ -51,5 +56,21 @@ cati("pi = $pi, e = `exp(1)`\\n") # split out numbers strapply("12abc34 55", "[0-9]+") +fn$optim(1, ~ x^2, method = "CG") + +fn$integrate(~ sin(x) + sin(x), 0, pi/2) + +fn$lapply(list(1:4, 1:5), ~ LETTERS[x]) + +fn$mapply(~ seq_len(x) + y * z, 1:3, 4:6, 2) # list(9, 11:12, 13:15) + +# must specify x since . is a free variable +fn$by(CO2[4:5], CO2[1], x ~ coef(lm(uptake ~ ., x)), simplify = rbind) + +# evaluate f at x^2 where f may be function or formula +square <- function(f, x, ...) { f <- match.funfn(f); f(x^2, ...) } +square(~ exp(x)/x, pi) +square(function(x) exp(x)/x, pi) # same + } \keyword{ package } diff --git a/man/gsubfn.Rd b/man/gsubfn.Rd index c93d378..35c8319 100755 --- a/man/gsubfn.Rd +++ b/man/gsubfn.Rd @@ -10,7 +10,6 @@ \usage{ gsubfn(pattern, replacement, x, backref, USE.NAMES = FALSE, env = parent.frame(), ...) } -%- maybe also 'usage' for other objects documented here. \arguments{ \item{pattern}{ Same as \code{pattern} in \code{\link{gsub}} } \item{replacement}{ A function or a formula. See Details. } @@ -39,45 +38,39 @@ Normally this is left at its default value.} As in \code{\link{gsub}}. } \seealso{ \code{\link{gsub}}, \code{\link{strapply}} } + \examples{ + # adds 1 to each number in third arg +gsubfn("[[:digit:]]+", function(x) as.numeric(x)+1, "(10 20)(100 30)") + +# same but using formula notation for function gsubfn("[[:digit:]]+", ~ as.numeric(x)+1, "(10 20)(100 30)") # replaces pairs m:n with their sum -g <- function(z,x,y) as.numeric(x)+as.numeric(y) -gsubfn("([0-9]+):([0-9]+)", g, "abc 10:20 def 30:40 50") - +s <- "abc 10:20 def 30:40 50" +gsubfn("([0-9]+):([0-9]+)", z + x + y ~ as.numeric(x) + as.numeric(y), s) # same - can reduce args in function to two using backref = -2 -f <- function(x,y) as.numeric(x)+as.numeric(y) -gsubfn("([0-9]+):([0-9]+)", f, "abc 10:20 def 30:40 50", backref = -2) +gsubfn("([0-9]+):([0-9]+)", ~ as.numeric(x) + as.numeric(y), s, backref = -2) -# same but uses formula in place of function -gsubfn("([0-9]+):([0-9]+)", ~ as.numeric(x) + as.numeric(y), backref = -2, - "abc 10:20 def 30:40 50") - -gsubfn( , , "pi = $pi, 2pi = `2*pi`") +# default pattern for gsubfn does quasi-perl-style string interpolation +gsubfn( , , "pi = \\$pi, 2pi = `2*pi`") # Extracts numbers from string and places them into numeric vector v. -# Also see ?strapply +# Normally this would be done in strapply instead. v <- c(); f <- function(x) v <<- append(v,as.numeric(x)) junk <- gsubfn("[0-9]+", f, "12;34:56,89,,12") v +# same +strapply("12;34:56,89,,12", "[0-9]+", simplify = c) + # makes all letters except first in word lower case -gsubfn("\\\\B.", tolower, "I LIKE A BANANA SPLIT") +gsubfn("\\\\B.", tolower, "I LIKE A BANANA SPLIT", perl = TRUE) # replaces numbers with that many Xs -repx <- function(n) paste(rep("X", n), collapse = "") -gsubfn("[[:digit:]]+", repx, "5.2") - -# given number followed by SI scale letter (e.g. 32.5k where k means 1000) -# replace letter with E followed by appropriate digit (3 in this example). -# conv vector is from formatEng2R by Hans-Joerg Bibiko (see R wiki) -conv <- paste0("E", c(seq(-24 ,-3, by=3), -1, -2, seq(3, 24, by=3))) -names(conv) <- c("y","z","a","f","p","n", - "µ","m","d","c","k","M","G","T","P","E","Z","Y") -gsubfn(".$", function(x) conv[[x]], "32.5k") # "32.5E3" +gsubfn("[[:digit:]]+", ~ paste(rep("X", n)), "5.2") } diff --git a/man/strapply.Rd b/man/strapply.Rd index fbc1c51..5ad0a30 100755 --- a/man/strapply.Rd +++ b/man/strapply.Rd @@ -38,7 +38,7 @@ backreferences, if any, are passed to the function \code{"FUN"} and the output is returned as a list. } \value{ -A list of character strings. +A list of character strings. } \seealso{ See Also as \code{\link{gsubfn}}, \code{\link{sapply}}} \examples{ @@ -58,6 +58,15 @@ strapply(s, "^([[:digit:]]+)(.*)", ~ data.frame(string, digits, rest), x <- "abcdefghijkl" strapply(x, "(.)(?=(....))", paste0, backref = -2, perl = TRUE)[[1]] +# Note difference. First gives character vector. Second is the same. +# Third has same elements but is a list. +# Fourth gives list of two character vectors. Fifth is the same. +strapply("a:b c:d", "(.):(.)", c)[[1]] +strapply("a:b c:d", "(.):(.)", list, simplify = unlist) # same +strapply("a:b c:d", "(.):(.)", list)[[1]] +strapply("a:b c:d", "(.):(.)", ~ list(c(...)))[[1]] +strapply("a:b c:d", "(.):(.)", ~ list(c(...)), simplify = c) + # find second CPU_SPEED value given lines of config file Lines <- c("DEVICE = 'PC'", "CPU_SPEED = '1999', '233'") parms <- strapply(Lines, "[^ ',=]+", c, USE.NAMES = TRUE)