Skip to content

Commit

Permalink
0.2.0.900 get_ functions
Browse files Browse the repository at this point in the history
  • Loading branch information
hrbrmstr committed Jun 17, 2015
1 parent 093df08 commit 725f686
Show file tree
Hide file tree
Showing 14 changed files with 362 additions and 22 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: omdbapi
Title: Tools to Access Movie, Television and Game Data from the 'Open Movie Database'
Version: 0.1.0.9000
Version: 0.2.0.9000
Authors@R: c(person("Bob", "Rudis", email = "[email protected]", role = c("aut", "cre")))
Description: Provides API access to the 'Open Movie Database' which maintains metadata
about movies, games and television shows through a public API.
Expand Down
6 changes: 6 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,14 @@
S3method(print,omdb)
export(find_by_id)
export(find_by_title)
export(get_actors)
export(get_countries)
export(get_directors)
export(get_genres)
export(get_writers)
export(search_by_title)
import(dplyr)
import(httr)
importFrom(stringr,str_pad)
importFrom(stringr,str_split)
importFrom(stringr,str_wrap)
109 changes: 109 additions & 0 deletions R/gets.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,109 @@
#' Get actors from an omdb object as a vector
#'
#' Splits the field at commas and returns a vector of individual entries
#'
#' @param omdb an object returned by \code{find_by_title} or \code{find_by_id}
#' @export
#' @return A character vector of actors
#' @examples
#' get_actors(find_by_id("tt0031381"))
get_actors <- function(omdb) {

if (!inherits(omdb, "omdb")) {
message("get_actors() expects an omdb object")
return(NULL)
}

if ("Actors" %in% names(omdb)) {
str_split(omdb$Actors, ",[ ]*")[[1]]
}

}

#' Get directors from an omdb object as a vector
#'
#' Splits the field at commas and returns a vector of individual entries
#'
#' @param omdb an object returned by \code{find_by_title} or \code{find_by_id}
#' @export
#' @return A character vector of directors
#' @examples
#' get_directors(find_by_id("tt0031381"))
get_directors <- function(omdb) {

if (!inherits(omdb, "omdb")) {
message("get_directors() expects an omdb object")
return(NULL)
}

if ("Director" %in% names(omdb)) {
str_split(omdb$Director, ",[ ]*")[[1]]
}

}

#' Get writers from an omdb object as a vector
#'
#' Splits the field at commas and returns a vector of individual entries
#'
#' @param omdb an object returned by \code{find_by_title} or \code{find_by_id}
#' @export
#' @return A character vector of writers
#' @examples
#' get_writers(find_by_id("tt0031381"))
get_writers <- function(omdb) {

if (!inherits(omdb, "omdb")) {
message("get_writers() expects an omdb object")
return(NULL)
}

if ("Writer" %in% names(omdb)) {
str_split(omdb$Writer, ",[ ]*")[[1]]
}

}

#' Get countries from an omdb object as a vector
#'
#' Splits the field at commas and returns a vector of individual entries
#'
#' @param omdb an object returned by \code{find_by_title} or \code{find_by_id}
#' @export
#' @return A character vector of countries
#' @examples
#' get_countries(find_by_id("tt0031381"))
get_countries <- function(omdb) {

if (!inherits(omdb, "omdb")) {
message("get_countries() expects an omdb object")
return(NULL)
}

if ("Country" %in% names(omdb)) {
str_split(omdb$Country, ",[ ]*")[[1]]
}

}

#' Get genres from an omdb object as a vector
#'
#' Splits the field at commas and returns a vector of individual entries
#'
#' @param omdb an object returned by \code{find_by_title} or \code{find_by_id}
#' @export
#' @return A character vector of genres
#' @examples
#' get_genres(find_by_id("tt0031381"))
get_genres <- function(omdb) {

if (!inherits(omdb, "omdb")) {
message("get_genres() expects an omdb object")
return(NULL)
}

if ("Genre" %in% names(omdb)) {
str_split(omdb$Genre, ",[ ]*")[[1]]
}

}
1 change: 1 addition & 0 deletions R/omdbapi-package.r
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,5 @@
#' @import httr dplyr
#' @importFrom stringr str_pad
#' @importFrom stringr str_wrap
#' @importFrom stringr str_split
NULL
33 changes: 23 additions & 10 deletions R/title_or_id.R
Original file line number Diff line number Diff line change
Expand Up @@ -47,11 +47,12 @@ find_by_title <- function(title, type=NULL, season=NULL, episode=NULL,
}

ret <- as_data_frame(tmp)
tmp[ tmp == "N/A" ] <- NA
class(ret) <- c("omdb", class(ret))
ret

}
suppressWarnings(fix_omdb(ret))

}

#' Retrieve OMDB info by IMDB ID search
#'
Expand Down Expand Up @@ -81,12 +82,12 @@ find_by_id <- function(id, type=NULL, year_of_release=NULL,
}

ret <- as_data_frame(tmp)
tmp[ tmp == "N/A" ] <- NA
class(ret) <- c("omdb", class(ret))
ret

}

suppressWarnings(fix_omdb(ret))

}

#' Lightweight omdb title search
#'
Expand Down Expand Up @@ -122,10 +123,13 @@ search_by_title <- function(term, type=NULL, year_of_release=NULL) {
#'
#' @param x omdb object
#' @param \dots ignored
#' @method print omdb
#' @export
print.omdb <- function(x, ...) {

cols <- setdiff(colnames(x[,which(x[,colnames(x)] != "N/A")]), "Response")
x <- as.data.frame(x, stringsAsFactors=FALSE)

cols <- setdiff(colnames(x[,which(!is.na(x[,colnames(x)]))]), "Response")

# all possible API returns

Expand All @@ -143,10 +147,19 @@ print.omdb <- function(x, ...) {

cat(str_pad(sprintf("%s: ", col), 2+max(nchar(cols))))

cat(paste(str_wrap(unlist(x[,col], use.names=FALSE),
width=options("width")$width-10,
exdent=nchar(str_pad(sprintf("%s: ", col), 2+max(nchar(cols))))),
collapse="\n"))
if (col %in% c("Released", "DVD")) {
cat(paste(str_wrap(format(x[,col], "%Y-%m-%d"),
width=options("width")$width-10,
exdent=nchar(str_pad(sprintf("%s: ", col), 2+max(nchar(cols))))),
collapse="\n"))

} else {
cat(paste(str_wrap(x[,col],
width=options("width")$width-10,
exdent=nchar(str_pad(sprintf("%s: ", col), 2+max(nchar(cols))))),
collapse="\n"))
}

cat("\n")

}
Expand Down
21 changes: 21 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@

fix_omdb <- function(x) {

if ("Released" %in% colnames(x)) x$Released <- as.Date(x$Released, format="%d %b %Y")
if ("DVD" %in% colnames(x)) x$DVD <- as.Date(x$DVD, format="%d %b %Y")

if ("imdbRating" %in% colnames(x)) x$imdbRating <- as.numeric(x$imdbRating)
if ("imdbVotes" %in% colnames(x)) x$imdbVotes <- as.numeric(gsub(",", "", x$imdbVotes))
if ("tomatoRating" %in% colnames(x)) x$tomatoRating <- as.numeric(x$tomatoRating)
if ("tomatoUserRating" %in% colnames(x)) x$tomatoUserRating <- as.numeric(x$tomatoUserRating)

if ("tomatoMeter" %in% colnames(x)) x$tomatoMeter <- as.integer(x$tomatoMeter)
if ("tomatoReviews" %in% colnames(x)) x$tomatoReviews <- as.integer(x$tomatoReviews)
if ("tomatoFresh" %in% colnames(x)) x$tomatoFresh <- as.integer(x$tomatoFresh)
if ("tomatoRotten" %in% colnames(x)) x$tomatoRotten <- as.integer(x$tomatoRotten)
if ("tomatoUserMeter" %in% colnames(x)) x$tomatoUserMeter <- as.numeric(x$tomatoUserMeter)
if ("tomatoUserReviews" %in% colnames(x)) x$tomatoUserReviews <- as.integer(x$tomatoUserReviews)

x

}
Binary file added README-usage-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
30 changes: 29 additions & 1 deletion README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,18 @@ The following functions are implemented:

- `find_by_id`: Retrieve OMDB info by IMDB ID search
- `find_by_title`: Retrieve OMDB info by title search
- `get_actors`: Get actors from an omdb object as a vector
- `get_countries`: Get countries from an omdb object as a vector
- `get_directors`: Get directors from an omdb object as a vector
- `get_genres`: Get genres from an omdb object as a vector
- `get_writers`: Get writers from an omdb object as a vector
- `print.omdb`: Print an omdb result
- `search_by_title`: Lightweight omdb title search

### News

- Version `0.1.0.9000` released
- Version `0.2.0.9000` released - better types in the data frames and `get_` methods to split the fields with multiple entries

### Installation

Expand All @@ -41,6 +47,8 @@ options(width=80)

```{r usage}
library(omdbapi)
library(dplyr)
library(pbapply)
# current verison
packageVersion("omdbapi")
Expand All @@ -50,11 +58,31 @@ search_by_title("Captain America")
search_by_title("Captain America", year_of_release=2013)
games <- search_by_title("Captain America", type="game")
print(games)
glimpse(games)
find_by_title(games$Title[1])
find_by_title("Game of Thrones", type="series", season=1, episode=1)
get_genres(find_by_title("Star Trek: Deep Space Nine", season=5, episode=7))
get_writers(find_by_title("Star Trek: Deep Space Nine", season=4, episode=6))
get_directors(find_by_id("tt1371111"))
get_countries(find_by_title("The Blind Swordsman: Zatoichi"))
ichi <- search_by_title("Zatoichi")
bind_rows(lapply(ichi$imdbID, function(x) {
find_by_id(x, include_tomatoes = TRUE)
})) -> zato
par(mfrow=c(3,1))
boxplot(zato$tomatoUserMeter, horizontal=TRUE, main="Tomato User Meter", ylim=c(0, 100))
boxplot(zato$imdbRating, horizontal=TRUE, main="IMDB Rating", ylim=c(0, 10))
boxplot(zato$tomatoUserRating, horizontal=TRUE, main="Tomato User Rating", ylim=c(0, 5))
par(mfrow=c(1,1))
```

### Test Results
Expand Down
Loading

0 comments on commit 725f686

Please sign in to comment.