R/GmapSnpDirectory-class.R
b22faf0d
 ### =========================================================================
 ### SnpDirectory class
 ### -------------------------------------------------------------------------
 ###
 ### Database of SNPs used by the GMAP suite.
 ###
 
 setClass("GmapSnpDirectory", representation(path = "character"))
 
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 ### Accessors
 ###
 
 setMethod("path", "GmapSnpDirectory", function(object) object@path)
 
 setMethod("names", "GmapSnpDirectory", function(x) {
   snp_files <- dir(path(x), ".*genomecomp\\.")
   sub("\\.genomecomp\\.", ":", snp_files)
 })
 
 setMethod("length", "GmapSnpDirectory", function(x) {
   length(names(x))
 })
 
753b566b
 setReplaceMethod("snps", c("GmapSnpDirectory", "character", "VCF"),
b22faf0d
                  function(x, name, genome = GmapGenome(genome(x)),
15766c62
                           iitPath = tempdir(), value)
b22faf0d
                  {
                    gr <- rowData(value)
                    values(gr) <- values(fixed(value))[c("REF", "ALT")]
                    iitFile <- file.path(iitPath, paste(name, "iit", sep = "."))
                    alt <- values(gr)$ALT
                    if (is(alt, "List")) {
d92a7992
                      gr <- rep(gr, elementNROWS(alt))
b22faf0d
                      alt <- unlist(alt)
                    }
                    ref <- values(gr)$REF
                    single <- nchar(alt) == 1L & nchar(ref) == 1L
                    change <- paste(ref[single], alt[single], sep = "")
                    gr <- gr[single]
                    values(gr) <- DataFrame(change)
                    export.iit(gr, iitFile)
                    snpindex(name, genome, path(x), iitFile)
                    x
                  })
 
753b566b
 setReplaceMethod("snps", c("GmapSnpDirectory", "character", "character"),
b22faf0d
                  function(x, name, genome, which, ..., value)
                  {
06642936
                    if (missing(genome)) {
                      stop("Please supply the \"genome\" argument")
                    }
 
b22faf0d
                    param <- ScanVcfParam(fixed = "ALT", info = NA, geno = NA)
f3db568b
                    if (!missing(which))
                      vcfWhich(param) <- which
753b566b
                    
b22faf0d
                    snps(x, name = name, genome = genome, ...) <-
                      readVcf(value, genome(genome), param)
                    x
                  })
 
 setMethod("[[<-", c("GmapSnpDirectory", value="ANY"),
           function(x, i, j, ..., value) {
             if (!missing(j))
               warning("argument 'j' ignored")
             snps(x, name = i, ...) <- value
             x
           })
 
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 ### Constructor
 ###
 
 GmapSnpDirectory <- function(path, create = FALSE) {
   if (is(path, "GmapGenome"))
     path <- path(path)
   if (!isSingleString(path))
     stop("'path' must be a single, non-NA string")
   if (!isTRUEorFALSE(create))
     stop("'create' must be TRUE or FALSE")
   if (create) {
     if (file.exists(path))
       message("NOTE: snp directory '", path, "' already exists, not recreating")
     else dir.create(path, recursive = TRUE)
   }
   new("GmapSnpDirectory", path = path)
 }
 
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 ### Show
 ###
 
 setMethod("show", "GmapSnpDirectory", function(object) {
   cat("GmapSnpDirectory object\n", "path: ", path(object),
       "\nnames: ", names(object), "\n", sep = "")
 })