Migrate to S4 Classes

Change-Id: I27e9452e9d59f6b414898390074908ec0e91e2a9
diff --git a/R/KorAPConnection.R b/R/KorAPConnection.R
index 85b12e4..84aec06 100644
--- a/R/KorAPConnection.R
+++ b/R/KorAPConnection.R
@@ -1,28 +1,63 @@
-#' @import jsonlite
-#' @import curl
-#' @import utils
-
-defaultKorAPUrl <- "https://korap.ids-mannheim.de/"
-
-#' Connect to a KorAP server.
+#' Class KorAPConnection
 #'
-#' @param KorAPUrl instead of providing the query and vc string parameters, you can also simply copy a KorAP query URL from your browser and use it here (and in \code{KorAPConnection}) to provide all necessary information for the query.
-#' @param apiVersion which version of KorAP's API you want to connect to
-#' @param apiUrl url of the KorAP web service
-#' @return object that contains all connection information and can be used with \code{\link{KorAPQuery}}
+#' \code{KorAPConnection} objetcs represent the connection to a KorAP server.
+#' New \code{KorAPConnection} objects can be created by \code{KorAPConnection()}
+#'
+#' @import jsonlite
+#' @import utils
+#' @import methods
+#'
+#'
+
+#' @export
+KorAPConnection <- setClass("KorAPConnection", slots=c(KorAPUrl="character", apiVersion="character", apiUrl="character"))
+
+#' @param .Object KorAPConnection object
+#' @param KorAPUrl the URL of the KorAP server instance you want to access.
+#' @param apiVersion which version of KorAP's API you want to connect to.
+#' @param apiUrl URL of the KorAP web service.
+#' @return \code{\link{KorAPConnection}} object that can be used e.g. with \code{\link{corpusQuery}}
+#'
+#' @examples
+#' kcon <- new("KorAPConnection")
+#' kq <- corpusQuery(kcon, "Ameisenplage")
+#' kq <- fetchAll(kq, verbose=TRUE)
 #'
 #' @note Currently it is not possible to authenticate the client
 #'
+#' @rdname KorAPConnection-class
 #' @export
-KorAPConnection <- function(KorAPUrl=defaultKorAPUrl, apiVersion='v1.0', apiUrl) {
-  m <-regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
-  KorAPUrl <- regmatches(KorAPUrl, m)
-  if (!endsWith(KorAPUrl, '/')) {
-    KorAPUrl <- paste0(KorAPUrl, "/")
-  }
-  if (missing(apiUrl)) {
-    apiUrl = paste0(KorAPUrl, 'api/', apiVersion, '/')
-  }
-  con <- data.frame(apiUrl, KorAPUrl, apiVersion)
-  return(con)
-}
+setMethod("initialize", "KorAPConnection",
+          function(.Object, KorAPUrl = "https://korap.ids-mannheim.de/", apiVersion = 'v1.0', apiUrl) {
+            .Object <- callNextMethod()
+            m <- regexpr("https?://[^?]+", KorAPUrl, perl = TRUE)
+            .Object@KorAPUrl <- regmatches(KorAPUrl, m)
+            if (!endsWith(.Object@KorAPUrl, '/')) {
+              .Object@KorAPUrl <- paste0(.Object@KorAPUrl, "/")
+            }
+            if (missing(apiUrl)) {
+              .Object@apiUrl = paste0(.Object@KorAPUrl, 'api/', apiVersion, '/')
+            } else {
+              .Object@apiUrl = apiUrl
+            }
+            .Object@apiVersion = apiVersion
+            .Object
+          })
+
+#' @rdname KorAPConnection-class
+#' @param object KorAPConnection object
+#' @export
+setMethod("show", "KorAPConnection", function(object) {
+  cat("<KorAPConnection>", "\n")
+  cat("apiUrl: ", object@apiUrl, "\n")
+})
+
+#' Funtion KorAPConnection()
+#'
+#' Wrappper function for new("KorAPConnection")
+#'
+#' @rdname KorAPConnection-constructor
+#' @name KorAPConnection-constructor
+#' @export
+# KorAPConnection <- function(...) new("KorAPConnection", ...)
+