The liftOver facilities developed in conjunction with the UCSC browser track infrastructure are available for transforming data in GRanges formats. This is illustrated here with an image of the NHGRI GWAS catalog that is, as of Oct. 31 2014, distributed with coordinates defined by NCBI build hg38.
library(gwascat)
cur = makeCurrentGwascat() # result varies by day
cur
## gwasloc instance with 17865 records and 35 attributes per record.
## Extracted: 2014-10-31
## Genome: GRCh38
## Excerpt:
## GRanges object with 5 ranges and 3 metadata columns:
## seqnames ranges strand |
## <Rle> <IRanges> <Rle> |
## [1] 17 [79831041, 79831041] * |
## [2] 5 [31766326, 31766326] * |
## [3] 11 [13107616, 13107616] * |
## [4] 10 [94922089, 94922089] * |
## [5] 10 [94922089, 94922089] * |
## Disease.Trait
## <character>
## [1] Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## [2] Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## [3] Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## [4] Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## [5] Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## SNPs p.Value
## <character> <numeric>
## [1] rs9747992 2e-07
## [2] rs2059865 3e-07
## [3] rs117020818 7e-07
## [4] rs1074145 4e-09
## [5] rs1074145 2e-16
## -------
## seqinfo: 23 sequences from GRCh38 genome
The transformation to hg19 coordinates is defined by a chain file provided by UCSC. rtracklayer::import.chain will bring the data into R.
library(rtracklayer)
## Loading required package: GenomicRanges
## Loading required package: BiocGenerics
## Loading required package: parallel
##
## Attaching package: 'BiocGenerics'
##
## The following objects are masked from 'package:parallel':
##
## clusterApply, clusterApplyLB, clusterCall, clusterEvalQ,
## clusterExport, clusterMap, parApply, parCapply, parLapply,
## parLapplyLB, parRapply, parSapply, parSapplyLB
##
## The following object is masked from 'package:stats':
##
## xtabs
##
## The following objects are masked from 'package:base':
##
## Filter, Find, Map, Position, Reduce, anyDuplicated, append,
## as.data.frame, as.vector, cbind, colnames, do.call,
## duplicated, eval, evalq, get, intersect, is.unsorted, lapply,
## mapply, match, mget, order, paste, pmax, pmax.int, pmin,
## pmin.int, rank, rbind, rep.int, rownames, sapply, setdiff,
## sort, table, tapply, union, unique, unlist, unsplit
##
## Loading required package: S4Vectors
## Loading required package: stats4
## Loading required package: IRanges
## Loading required package: GenomeInfoDb
ch = import.chain("hg38ToHg19.over.chain")
ch
## Chain of length 25
## names(25): chr22 chr21 chr19 chr20 chrY chr18 ... chr5 chr4 chr3 chr2 chr1
str(ch[[1]])
## Formal class 'ChainBlock' [package "rtracklayer"] with 6 slots
## ..@ ranges :Formal class 'IRanges' [package "IRanges"] with 6 slots
## .. .. ..@ start : int [1:6842] 16367189 16386933 16386970 16387001 16387128 16395491 16395528 16395841 16395860 16395956 ...
## .. .. ..@ width : int [1:6842] 19744 36 31 112 8362 36 312 18 95 33 ...
## .. .. ..@ NAMES : NULL
## .. .. ..@ elementType : chr "integer"
## .. .. ..@ elementMetadata: NULL
## .. .. ..@ metadata : list()
## ..@ offset : int [1:6842] -480662 -480702 -480702 -480726 -480726 -480726 -480726 -480726 -480726 -480726 ...
## ..@ score : int [1:1168] -1063867308 68830488 21156147 20814926 7358950 3927744 2928210 991419 880681 802146 ...
## ..@ space : chr [1:1168] "chr22" "chr14" "chr22" "chr21" ...
## ..@ reversed: logi [1:1168] FALSE FALSE FALSE FALSE FALSE FALSE ...
## ..@ length : int [1:1168] 1124 1280 173 465 398 110 43 173 342 84 ...
Some more details about the chain data structure are available in the import.chain man page
A chain file essentially details many local alignments, so it is possible for the "from" ranges to map to overlapping regions in the other sequence. The "from" ranges are guaranteed to be disjoint (but do not necessarily cover the entire "from" sequence).
The liftOver function will create a GRangesList.
seqlevelsStyle(cur) = "UCSC" # necessary
cur19 = liftOver(cur, ch)
class(cur19)
## [1] "GRangesList"
## attr(,"package")
## [1] "GenomicRanges"
We unlist and coerce to the gwaswloc class, a convenient form for the GWAS catalog with its many mcols fields.
cur19 = unlist(cur19)
genome(cur19) = "hg19"
cur19 = new("gwaswloc", cur19)
cur19
## gwasloc instance with 17845 records and 35 attributes per record.
## Extracted:
## Genome: hg19
## Excerpt:
## GRanges object with 5 ranges and 3 metadata columns:
## seqnames ranges strand |
## <Rle> <IRanges> <Rle> |
## 1 chr17 [77804840, 77804840] * |
## 2 chr5 [31766433, 31766433] * |
## 3 chr11 [13129163, 13129163] * |
## 4 chr10 [96681846, 96681846] * |
## 5 chr10 [96681846, 96681846] * |
## Disease.Trait
## <character>
## 1 Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## 2 Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## 3 Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## 4 Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## 5 Response to serotonin reuptake inhibitors in major depressive disorder (plasma drug and metabolite levels)
## SNPs p.Value
## <character> <numeric>
## 1 rs9747992 2e-07
## 2 rs2059865 3e-07
## 3 rs117020818 7e-07
## 4 rs1074145 4e-09
## 5 rs1074145 2e-16
## -------
## seqinfo: 23 sequences from hg19 genome; no seqlengths
We see that the translation leads to a loss of some loci.
length(cur)-length(cur19)
## [1] 20
setdiff(cur$SNPs, cur19$SNPs)
## [1] "rs687289" "rs386000" "rs718433" "rs4911642" "rs687621"
## [6] "rs757210" "rs11672691" "rs644234" "rs514659" "rs9876781"
## [11] "rs649129" "rs1167796" "rs644148"
It may be interesting to follow up some of the losses.