... | ... |
@@ -1,33 +1,76 @@ |
1 |
+#' @title Calculate on-target sgRNA activity scores for Cas9 using CRISPRater |
|
2 |
+#' @description Calculate on-target sgRNA activity scores for |
|
3 |
+#' CRISPR/Cas9-induced knockout using the DeepHF scoring method. Both U6 |
|
4 |
+#' and T7 promoters are supported. Three different versions of the SpCas9 |
|
5 |
+#' nuclease are supported: wildtype (WT-SpCas9), high-fidelity Cas9 |
|
6 |
+#' (SpCas9-HF1) and enhanced Cas9 (eSpCas9). Currently not supported |
|
7 |
+#' on Windows machines. |
|
8 |
+#' |
|
9 |
+#' @param sequences Character vector of 20bp protospacer sequences. |
|
10 |
+#' |
|
11 |
+#' @details Input sequences for CRISPRater scoring must be 20 spacer sequences. |
|
12 |
+#' |
|
13 |
+#' @return \strong{getCrisprRaterScores} returns a data.frame with |
|
14 |
+#' \code{sequence} and \code{score} columns. The CRISPRater score takes on |
|
15 |
+#' a value between 0 and 1. A higher score indicates higher knockout |
|
16 |
+#' efficiency. |
|
17 |
+#' |
|
18 |
+#' |
|
19 |
+#' @references |
|
20 |
+#' Labuhn M, Adams FF, Ng M, et al. Refined sgRNA efficacy prediction improves |
|
21 |
+#' large-and small-scale CRISPR–Cas9 applications. Nucleic acids research. 2018 |
|
22 |
+#' Feb 16;46(3):1375-85. |
|
23 |
+#' |
|
24 |
+#' @author Jean-Philippe Fortin |
|
25 |
+#' |
|
26 |
+#' @examples |
|
27 |
+#' spacer <- "ATCGATGCTGATGCTAGATA" #20bp |
|
28 |
+#' results <- getCRISPRaterScores(spacer) |
|
29 |
+#' |
|
30 |
+#' @export |
|
31 |
+getCRISPRaterScores <- function(sequences){ |
|
32 |
+ |
|
33 |
+ sequences <- .checkSequenceInputs(sequences) |
|
34 |
+ if (unique(nchar(sequences))!=20){ |
|
35 |
+ stop("Provided sequences must have length 20nt (20nt-spacer") |
|
36 |
+ } |
|
37 |
+ results <- .getModelScoreCRISPRater(sequences) |
|
38 |
+ return(results) |
|
39 |
+} |
|
40 |
+ |
|
1 | 41 |
|
2 | 42 |
|
3 | 43 |
# Must be 20nt long |
4 | 44 |
#spacers <- c("GGTGCTGATGCTGTGTGATG", |
5 | 45 |
# "GGTGCTGATAAAGTGTGATG") |
6 |
-.getModelScore <- function(spacers){ |
|
7 |
- features <- .extractFeatures(spacers) |
|
8 |
- score <- model_offset + model_weights%*%t(features) |
|
46 |
+.getModelScoreCRISPRater <- function(sequences){ |
|
47 |
+ |
|
48 |
+ model_weights <- c(0.14177385, |
|
49 |
+ 0.06966514, |
|
50 |
+ 0.04216254, |
|
51 |
+ 0.03303432, |
|
52 |
+ 0.02355430, |
|
53 |
+ -0.04746424, |
|
54 |
+ -0.04878001, |
|
55 |
+ -0.06981921, |
|
56 |
+ -0.07087756, |
|
57 |
+ -0.08160700) |
|
58 |
+ model_offset <- 0.6505037 |
|
59 |
+ |
|
60 |
+ features <- .extractFeaturesForCRISPRater(sequences) |
|
61 |
+ score <- model_offset + model_weights %*% t(features) |
|
9 | 62 |
return(score) |
10 | 63 |
} |
11 | 64 |
|
12 |
-model_weights <- c(0.14177385, |
|
13 |
- 0.06966514, |
|
14 |
- 0.04216254, |
|
15 |
- 0.03303432, |
|
16 |
- 0.02355430, |
|
17 |
- -0.04746424, |
|
18 |
- -0.04878001, |
|
19 |
- -0.06981921, |
|
20 |
- -0.07087756, |
|
21 |
- -0.08160700) |
|
22 |
-model_offset <- 0.6505037 |
|
65 |
+ |
|
23 | 66 |
|
24 | 67 |
|
25 | 68 |
#' @importFrom Biostrings DNAStringSet letterFrequency |
26 |
-.extractFeatures <- function(spacers){ |
|
27 |
- gc <- rowSums(letterFrequency(DNAStringSet(substr(spacers,4,14)), |
|
69 |
+.extractFeaturesForCRISPRater <- function(sequences){ |
|
70 |
+ gc <- rowSums(letterFrequency(DNAStringSet(substr(sequences,4,14)), |
|
28 | 71 |
c("G", "C")))/10 |
29 |
- spacers <- DNAStringSet(spacers) |
|
30 |
- mat <- as.matrix(DNAStringSet(spacers)) |
|
72 |
+ sequences <- DNAStringSet(sequences) |
|
73 |
+ mat <- as.matrix(DNAStringSet(sequences)) |
|
31 | 74 |
features <- list() |
32 | 75 |
features[[1]] <- gc |
33 | 76 |
features[[2]] <- mat[,20,drop=FALSE]=="G" |
... | ... |
@@ -9,4 +9,5 @@ deepcpf1 AsCas12a -4 29 On-target DeepCpf1 |
9 | 9 |
enpamgb enAsCas12a -4 29 On-target EnPAMGB |
10 | 10 |
crisprscan SpCas9 -26 8 On-target CRISPRscan |
11 | 11 |
casrxrf CasRx NA NA On-target CasRx-RF |
12 |
-crisprai SpCas9 -19 2 On-target CRISPRai |
|
13 | 12 |
\ No newline at end of file |
13 |
+crisprai SpCas9 -19 2 On-target CRISPRai |
|
14 |
+crisprater SpCas9 -20 -1 On-target CRISPRater |
|
14 | 15 |
\ No newline at end of file |
15 | 16 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,41 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/getCRISPRaterScores.R |
|
3 |
+\name{getCRISPRaterScores} |
|
4 |
+\alias{getCRISPRaterScores} |
|
5 |
+\title{Calculate on-target sgRNA activity scores for Cas9 using CRISPRater} |
|
6 |
+\usage{ |
|
7 |
+getCRISPRaterScores(sequences) |
|
8 |
+} |
|
9 |
+\arguments{ |
|
10 |
+\item{sequences}{Character vector of 20bp protospacer sequences.} |
|
11 |
+} |
|
12 |
+\value{ |
|
13 |
+\strong{getCrisprRaterScores} returns a data.frame with |
|
14 |
+ \code{sequence} and \code{score} columns. The CRISPRater score takes on |
|
15 |
+ a value between 0 and 1. A higher score indicates higher knockout |
|
16 |
+ efficiency. |
|
17 |
+} |
|
18 |
+\description{ |
|
19 |
+Calculate on-target sgRNA activity scores for |
|
20 |
+ CRISPR/Cas9-induced knockout using the DeepHF scoring method. Both U6 |
|
21 |
+ and T7 promoters are supported. Three different versions of the SpCas9 |
|
22 |
+ nuclease are supported: wildtype (WT-SpCas9), high-fidelity Cas9 |
|
23 |
+ (SpCas9-HF1) and enhanced Cas9 (eSpCas9). Currently not supported |
|
24 |
+ on Windows machines. |
|
25 |
+} |
|
26 |
+\details{ |
|
27 |
+Input sequences for CRISPRater scoring must be 20 spacer sequences. |
|
28 |
+} |
|
29 |
+\examples{ |
|
30 |
+spacer <- "ATCGATGCTGATGCTAGATA" #20bp |
|
31 |
+results <- getCRISPRaterScores(spacer) |
|
32 |
+ |
|
33 |
+} |
|
34 |
+\references{ |
|
35 |
+Labuhn M, Adams FF, Ng M, et al. Refined sgRNA efficacy prediction improves |
|
36 |
+large-and small-scale CRISPR–Cas9 applications. Nucleic acids research. 2018 |
|
37 |
+Feb 16;46(3):1375-85. |
|
38 |
+} |
|
39 |
+\author{ |
|
40 |
+Jean-Philippe Fortin |
|
41 |
+} |
... | ... |
@@ -2,13 +2,13 @@ |
2 | 2 |
title: "On-target and off-target scoring for CRISPR/Cas systems" |
3 | 3 |
author: |
4 | 4 |
- name: Jean-Philippe Fortin |
5 |
- affiliation: OMNI Bioinformatics, gRED, Genentech |
|
5 |
+ affiliation: Data Science and Statistical Computing, gRED, Genentech |
|
6 | 6 |
email: [email protected] |
7 | 7 |
- name: Aaron Lun |
8 |
- affiliation: Data Science Statistical Computing, gRED, Genentech |
|
8 |
+ affiliation: Data Science and Statistical Computing, gRED, Genentech |
|
9 | 9 |
email: [email protected] |
10 | 10 |
- name: Luke Hoberecht |
11 |
- affiliation: OMNI Bioinformatics, gRED, Genentech |
|
11 |
+ affiliation: Data Science and Statistical Computing, gRED, Genentech |
|
12 | 12 |
email: [email protected] |
13 | 13 |
date: "`r Sys.Date()`" |
14 | 14 |
output: |
... | ... |
@@ -59,11 +59,16 @@ file in order for `crisprScore` to work properly: |
59 | 59 |
options(reticulate.useImportHook=FALSE) |
60 | 60 |
``` |
61 | 61 |
|
62 |
+We load `crisprScore` in the usual way: |
|
63 |
+ |
|
64 |
+```{r, warnings=FALSE, message=FALSE} |
|
65 |
+library(crisprScore) |
|
66 |
+``` |
|
67 |
+ |
|
62 | 68 |
The `scoringMethodsInfo` data.frame contains a succinct summary of scoring |
63 | 69 |
methods available in `crisprScore`: |
64 | 70 |
|
65 | 71 |
```{r} |
66 |
-library(crisprScore) |
|
67 | 72 |
data(scoringMethodsInfo) |
68 | 73 |
print(scoringMethodsInfo) |
69 | 74 |
``` |
... | ... |
@@ -74,21 +79,21 @@ See `?scoringMethodsInfo` for more information about the different columns. |
74 | 79 |
|
75 | 80 |
Predicting on-target cutting efficiency is an extensive area of research, and |
76 | 81 |
we try to provide in `crisprScore` the latest state-of-the-art algorithms as |
77 |
-they become available. Different algorithms require different input nucleotide |
|
78 |
-sequences to predict cutting efficiency as illustrated in the two |
|
79 |
-figures below. |
|
82 |
+they become available. |
|
83 |
+ |
|
84 |
+## Cas9 methods |
|
80 | 85 |
|
86 |
+Different algorithms require different input nucleotide |
|
87 |
+sequences to predict cutting efficiency as illustrated in the figure below. |
|
81 | 88 |
|
82 | 89 |
```{r, echo=FALSE,fig.cap="Sequence inputs for Cas9 scoring methods"} |
83 | 90 |
knitr::include_graphics("./figures/sequences_cas9.svg") |
84 | 91 |
``` |
85 | 92 |
|
86 |
-```{r, echo=FALSE, fig.cap="Sequence inputs for Cas12a scoring methods"} |
|
87 |
-knitr::include_graphics("./figures/sequences_cas12a.svg") |
|
88 |
-``` |
|
89 | 93 |
|
90 | 94 |
|
91 |
-## Rule Set 1 (Cas9) |
|
95 |
+ |
|
96 |
+### Rule Set 1 (SpCas9) |
|
92 | 97 |
|
93 | 98 |
The Rule Set 1 algorithm is one of the first on-target efficiency methods |
94 | 99 |
developed for the Cas9 nuclease [@ruleset1]. It generates a probability |
... | ... |
@@ -108,7 +113,7 @@ results <- getRuleSet1Scores(input) |
108 | 113 |
The Azimuth score described below is an improvement over Rule Set 1 |
109 | 114 |
from the same lab. |
110 | 115 |
|
111 |
-## Azimuth score (Cas9) |
|
116 |
+### Azimuth score (SpCas9) |
|
112 | 117 |
|
113 | 118 |
The Azimuth algorithm is an improved version of the popular Rule Set 2 score for |
114 | 119 |
the Cas9 nuclease [@azimuth]. It generates a probability (therefore a score |
... | ... |
@@ -125,7 +130,7 @@ input <- paste0(flank5, spacer, pam, flank3) |
125 | 130 |
results <- getAzimuthScores(input) |
126 | 131 |
``` |
127 | 132 |
|
128 |
-## DeepHF score (Cas9) |
|
133 |
+### DeepHF score (SpCas9, HF-SpCas9) |
|
129 | 134 |
|
130 | 135 |
The DeepHF algorithm is an on-target cutting efficiency prediction algorithm for |
131 | 136 |
several variants of the Cas9 nuclease [@deepcas9] using a recurrent neural |
... | ... |
@@ -148,7 +153,95 @@ also specify the promoter used for expressing sgRNAs using the argument |
148 | 153 |
`promoter` ("U6" by default). See `?getDeepHFScores` for more details. |
149 | 154 |
|
150 | 155 |
|
151 |
-## DeepCpf1 score (Cas12a) |
|
156 |
+ |
|
157 |
+ |
|
158 |
+ |
|
159 |
+ |
|
160 |
+ |
|
161 |
+ |
|
162 |
+### CRISPRscan (Moreno-Mateos score, SpCas9) |
|
163 |
+ |
|
164 |
+The CRISPRscan algorithm, also known as the Moreno-Mateos score), is an |
|
165 |
+on-target efficiency method for the SpCas9 nuclease developed for sgRNAs |
|
166 |
+expressed from a T7 promoter, and trained on zebrafish data [@crisprscan]. |
|
167 |
+It generates a probability (therefore a score between 0 and 1) that a given |
|
168 |
+sgRNA will cut at its intended target. |
|
169 |
+6 nucleotides upstream of the protospacer sequence |
|
170 |
+and 6 nucleotides downstream of the PAM sequence are needed for scoring: |
|
171 |
+ |
|
172 |
+```{r, eval=TRUE} |
|
173 |
+flank5 <- "ACCTAA" #6bp |
|
174 |
+spacer <- "ATCGATGCTGATGCTAGATA" #20bp |
|
175 |
+pam <- "AGG" #3bp |
|
176 |
+flank3 <- "TTGAAT" #6bp |
|
177 |
+input <- paste0(flank5, spacer, pam, flank3) |
|
178 |
+results <- getCRISPRscanScores(input) |
|
179 |
+``` |
|
180 |
+ |
|
181 |
+ |
|
182 |
+ |
|
183 |
+### CRISPRater (SpCas9) |
|
184 |
+ |
|
185 |
+The CRISPRater algorithm is an on-target efficiency method for the SpCas9 nuclease [@crisprater]. |
|
186 |
+It generates a probability (therefore a score between 0 and 1) that a given |
|
187 |
+sgRNA will cut at its intended target. |
|
188 |
+Only the 20bp spacer sequence is required. |
|
189 |
+ |
|
190 |
+```{r, eval=TRUE} |
|
191 |
+spacer <- "ATCGATGCTGATGCTAGATA" #20bp |
|
192 |
+results <- getCRISPRaterScores(spacer) |
|
193 |
+``` |
|
194 |
+ |
|
195 |
+### CRISPRai (SpCas9) |
|
196 |
+ |
|
197 |
+The CRISPRai algorithm was developed by the Weissman lab to score SpCas9 gRNAs for CRISPRa and CRISPRi applications [@crisprai], for the human genome. The function `getCrispraiScores` requires several inputs. |
|
198 |
+ |
|
199 |
+First, it requires a data.frame specifying the genomic coordinates of the transcription starting sites (TSSs). |
|
200 |
+An example of such a data.frame is provided in the crisprScore package: |
|
201 |
+ |
|
202 |
+```{r, eval=TRUE} |
|
203 |
+head(tssExampleCrispri) |
|
204 |
+``` |
|
205 |
+ |
|
206 |
+It also requires a data.frame specifying the genomic coordinates of the gRNA sequences to score. An example of such a data.frame is provided in the crisprScore package: |
|
207 |
+ |
|
208 |
+```{r, eval=TRUE} |
|
209 |
+head(sgrnaExampleCrispri) |
|
210 |
+``` |
|
211 |
+ |
|
212 |
+All columns present in `tssExampleCrispri` and `sgrnaExampleCrispri` are mandatory for `getCrispraiScores` to work. |
|
213 |
+ |
|
214 |
+Two additional arguments are required: `fastaFile`, to specify the path of the fasta file of the human reference genome, and `chromatinFiles`, which is a list specifying the path of files containing chromatin accessibility genomic tracks in hg38 coordinates. The chromatin files can be downloaded from Zenodo at the following link: [Currently being uploaded]. |
|
215 |
+The fasta file for the human genome (hg38) can be dowloaded directly from here: |
|
216 |
+https://hgdownload.soe.ucsc.edu/goldenPath/hg38/bigZips/hg38.fa.gz |
|
217 |
+ |
|
218 |
+ |
|
219 |
+ |
|
220 |
+One can obtain the CRISPRai scores using the following command: |
|
221 |
+ |
|
222 |
+```{r, eval=FALSE} |
|
223 |
+results <- getCrispraiScores(tss_df=tssExampleCrispri, |
|
224 |
+ sgrna_df=sgrnaExampleCrispri, |
|
225 |
+ modality="CRISPRi", |
|
226 |
+ fastaFile="your/path/hg38.fa", |
|
227 |
+ chromatinFiles=list(mnase="path/to/mnaseFile.bw", |
|
228 |
+ dnase="path/to/dnaseFile.bw", |
|
229 |
+ faire="oath/to/faireFile.bw")) |
|
230 |
+``` |
|
231 |
+ |
|
232 |
+The function works identically for CRISPRa applications, with modality replaced |
|
233 |
+by `CRISPRa`. |
|
234 |
+ |
|
235 |
+## Cas12a methods |
|
236 |
+ |
|
237 |
+Different algorithms require different input nucleotide |
|
238 |
+sequences to predict cutting efficiency as illustrated in the figure below. |
|
239 |
+ |
|
240 |
+```{r, echo=FALSE, fig.cap="Sequence inputs for Cas12a scoring methods"} |
|
241 |
+knitr::include_graphics("./figures/sequences_cas12a.svg") |
|
242 |
+``` |
|
243 |
+ |
|
244 |
+### DeepCpf1 score (AsCas12a) |
|
152 | 245 |
|
153 | 246 |
The DeepCpf1 algorithm is an on-target cutting efficiency prediction algorithm |
154 | 247 |
for the Cas12a nuclease [@deepcpf1] using a convolutional neural network (CNN) |
... | ... |
@@ -166,10 +259,7 @@ input <- paste0(flank5, pam, spacer, flank3) |
166 | 259 |
results <- getDeepCpf1Scores(input) |
167 | 260 |
``` |
168 | 261 |
|
169 |
- |
|
170 |
- |
|
171 |
- |
|
172 |
-## enPAM+GB score (enCas12a) |
|
262 |
+### enPAM+GB score (enCas12a) |
|
173 | 263 |
|
174 | 264 |
The enPAM+GB algorithm is an on-target cutting efficiency prediction algorithm |
175 | 265 |
for the enhanced Cas12a (enCas12a) nuclease [@enpamgb] using a gradient-booster |
... | ... |
@@ -189,23 +279,25 @@ input <- paste0(flank5, pam, spacer, flank3) |
189 | 279 |
results <- getEnPAMGBScores(input) |
190 | 280 |
``` |
191 | 281 |
|
192 |
-## CRISPRscan (Moreno-Mateos score) |
|
193 | 282 |
|
194 |
-The CRISPRscan algorithm, also known as the Moreno-Mateos score), is an |
|
195 |
-on-target efficiency method for the SpCas9 nuclease developed for sgRNAs |
|
196 |
-expressed from a T7 promoter, and trained on zebrafish data [@crisprscan]. |
|
197 |
-It generates a probability (therefore a score between 0 and 1) that a given |
|
198 |
-sgRNA will cut at its intended target. |
|
199 |
-6 nucleotides upstream of the protospacer sequence |
|
200 |
-and 6 nucleotides downstream of the PAM sequence are needed for scoring: |
|
283 |
+## Cas13d methods |
|
201 | 284 |
|
202 |
-```{r, eval=TRUE} |
|
203 |
-flank5 <- "ACCTAA" #6bp |
|
204 |
-spacer <- "ATCGATGCTGATGCTAGATA" #20bp |
|
205 |
-pam <- "AGG" #3bp |
|
206 |
-flank3 <- "TTGAAT" #6bp |
|
207 |
-input <- paste0(flank5, spacer, pam, flank3) |
|
208 |
-results <- getCRISPRscanScores(input) |
|
285 |
+### CasRxRF (RfxCas13d) |
|
286 |
+ |
|
287 |
+The CasRxRF method was developed to characterize on-target efficiency of the RNA-targeting nuclease RfxCas13d, abbreviated as CasRx [@casrxrf]. |
|
288 |
+ |
|
289 |
+It requires as an input the mRNA sequence targeted by the gRNAs, and returns as an output on-target efficiency scores for all gRNAs targeting the mRNA sequence. |
|
290 |
+ |
|
291 |
+As an example, we predict on-target efficiency for gRNAs targeting the mRNA sequence stored in the file `test.fa`: |
|
292 |
+ |
|
293 |
+ |
|
294 |
+```{r, eval=FALSE} |
|
295 |
+fasta <- file.path(system.file(package="crisprScore"), |
|
296 |
+ "casrxrf/test.fa") |
|
297 |
+mrnaSequence <- Biostrings::readDNAStringSet(filepath=fasta |
|
298 |
+ format="fasta", |
|
299 |
+ use.names=TRUE) |
|
300 |
+results <- getCasRxRFScores(mrnaSequence) |
|
209 | 301 |
``` |
210 | 302 |
|
211 | 303 |
|
... | ... |
@@ -6,575 +6,691 @@ |
6 | 6 |
id="svg2" |
7 | 7 |
xml:space="preserve" |
8 | 8 |
width="1296" |
9 |
- height="480" |
|
10 |
- viewBox="0 0 1296 480" |
|
9 |
+ height="498.66666" |
|
10 |
+ viewBox="0 0 1296 498.66666" |
|
11 | 11 |
xmlns="http://www.w3.org/2000/svg" |
12 | 12 |
xmlns:svg="http://www.w3.org/2000/svg"><defs |
13 | 13 |
id="defs6"><clipPath |
14 | 14 |
clipPathUnits="userSpaceOnUse" |
15 | 15 |
id="clipPath18"><path |
16 |
- d="M 0,8.046627e-6 H 971.76 V 360.00001 H 0 Z" |
|
16 |
+ d="M 0,0.08000836 H 971.76 V 374.00001 H 0 Z" |
|
17 | 17 |
id="path16" /></clipPath></defs><g |
18 | 18 |
id="g8" |
19 |
- transform="matrix(1.3333333,0,0,-1.3333333,0,480)"><g |
|
19 |
+ transform="matrix(1.3333333,0,0,-1.3333333,0,498.66667)"><g |
|
20 | 20 |
id="g10" /><g |
21 | 21 |
id="g12"><g |
22 | 22 |
id="g14" |
23 | 23 |
clip-path="url(#clipPath18)"><path |
24 |
- d="M 0,360 H 971.76 V 8.046627e-6 H 0 Z" |
|
24 |
+ d="M 0,374 H 971.76 V 0.08000836 H 0 Z" |
|
25 | 25 |
style="fill:#ffffff;fill-opacity:1;fill-rule:nonzero;stroke:none" |
26 | 26 |
id="path20" /></g></g><g |
27 | 27 |
id="g22"><path |
28 |
- d="M 0,360 H 972 V 9.387731e-6 H 0 Z" |
|
28 |
+ d="M 0,374 H 972 V -0.3750296 H 0 Z" |
|
29 | 29 |
style="fill:#ffffff;fill-opacity:1;fill-rule:nonzero;stroke:none" |
30 | 30 |
id="path24" /><g |
31 | 31 |
id="g26" |
32 |
- transform="matrix(0.24,0,0,0.24,355.1134,-126)"><text |
|
33 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
32 |
+ transform="matrix(0.24,0,0,0.24,355.1134,-177.28)"><text |
|
33 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
34 | 34 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
35 | 35 |
id="text30"><tspan |
36 | 36 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
37 | 37 |
y="0" |
38 | 38 |
id="tspan28">ATCGATGCTGATGCTA</tspan></text></g><g |
39 | 39 |
id="g32" |
40 |
- transform="matrix(0.24,0,0,0.24,595.1134,-126)"><text |
|
41 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
40 |
+ transform="matrix(0.24,0,0,0.24,595.1134,-177.28)"><text |
|
41 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
42 | 42 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
43 | 43 |
id="text36"><tspan |
44 | 44 |
x="0" |
45 | 45 |
y="0" |
46 | 46 |
id="tspan34">G</tspan></text></g><g |
47 | 47 |
id="g38" |
48 |
- transform="matrix(0.24,0,0,0.24,610.1134,-126)"><text |
|
49 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
48 |
+ transform="matrix(0.24,0,0,0.24,610.1134,-177.28)"><text |
|
49 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
50 | 50 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
51 | 51 |
id="text42"><tspan |
52 | 52 |
x="0 62.500019 125.00004" |
53 | 53 |
y="0" |
54 | 54 |
id="tspan40">ATA</tspan></text></g><g |
55 | 55 |
id="g44" |
56 |
- transform="matrix(0.24,0,0,0.24,655.1134,-126)"><text |
|
57 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
56 |
+ transform="matrix(0.24,0,0,0.24,655.1134,-177.28)"><text |
|
57 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
58 | 58 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
59 | 59 |
id="text48"><tspan |
60 | 60 |
x="0" |
61 | 61 |
y="0" |
62 | 62 |
id="tspan46">A</tspan></text></g><g |
63 | 63 |
id="g50" |
64 |
- transform="matrix(0.24,0,0,0.24,670.1134,-126)"><text |
|
65 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
64 |
+ transform="matrix(0.24,0,0,0.24,670.1134,-177.28)"><text |
|
65 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
66 | 66 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
67 | 67 |
id="text54"><tspan |
68 | 68 |
x="0 62.500019" |
69 | 69 |
y="0" |
70 | 70 |
id="tspan52">GG</tspan></text></g><g |
71 | 71 |
id="g56" |
72 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.421,240.6492)"><path |
|
72 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4213,203.41)"><path |
|
73 | 73 |
d="M 0,0 2785439,1" |
74 | 74 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
75 | 75 |
id="path58" /></g><g |
76 | 76 |
id="g60" |
77 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,207.5347)"><path |
|
77 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,173.3378)"><path |
|
78 | 78 |
d="M 0,0 2054114,1" |
79 | 79 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
80 | 80 |
id="path62" /></g><g |
81 | 81 |
id="g64" |
82 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,709.5364,240.6492)"><path |
|
82 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,709.5367,203.41)"><path |
|
83 | 83 |
d="M 0,0 2573401,1" |
84 | 84 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
85 | 85 |
id="path66" /></g><g |
86 | 86 |
id="g68" |
87 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,755.3,207.5347)"><path |
|
87 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,755.3003,173.3378)"><path |
|
88 | 88 |
d="M 0,0 1992203,1" |
89 | 89 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
90 | 90 |
id="path70" /></g><g |
91 | 91 |
id="g72" |
92 |
- transform="matrix(0.24,0,0,0.24,50.45334,-123.36)"><text |
|
93 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
92 |
+ transform="matrix(0.24,0,0,0.24,50.45397,-174.64)"><text |
|
93 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
94 | 94 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
95 | 95 |
id="text76"><tspan |
96 | 96 |
x="0 46.357498 83.864998 121.3725 160.98 207.8625" |
97 | 97 |
y="0" |
98 | 98 |
id="tspan74">DeepHF</tspan></text></g><g |
99 | 99 |
id="g78" |
100 |
- transform="matrix(0.24,0,0,0.24,295.3618,-159.6)"><text |
|
101 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
100 |
+ transform="matrix(0.24,0,0,0.24,295.3618,-207.76)"><text |
|
101 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
102 | 102 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
103 | 103 |
id="text82"><tspan |
104 | 104 |
x="0 62.500019 125.00004 187.50006" |
105 | 105 |
y="0" |
106 | 106 |
id="tspan80">ACCT</tspan></text></g><g |
107 | 107 |
id="g84" |
108 |
- transform="matrix(0.24,0,0,0.24,355.3618,-159.6)"><text |
|
109 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
108 |
+ transform="matrix(0.24,0,0,0.24,355.3618,-207.76)"><text |
|
109 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
110 | 110 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
111 | 111 |
id="text88"><tspan |
112 | 112 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
113 | 113 |
y="0" |
114 | 114 |
id="tspan86">ATCGATGCTGATGCTA</tspan></text></g><g |
115 | 115 |
id="g90" |
116 |
- transform="matrix(0.24,0,0,0.24,595.3618,-159.6)"><text |
|
117 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
116 |
+ transform="matrix(0.24,0,0,0.24,595.3618,-207.76)"><text |
|
117 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
118 | 118 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
119 | 119 |
id="text94"><tspan |
120 | 120 |
x="0" |
121 | 121 |
y="0" |
122 | 122 |
id="tspan92">G</tspan></text></g><g |
123 | 123 |
id="g96" |
124 |
- transform="matrix(0.24,0,0,0.24,610.3618,-159.6)"><text |
|
125 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
124 |
+ transform="matrix(0.24,0,0,0.24,610.3618,-207.76)"><text |
|
125 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
126 | 126 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
127 | 127 |
id="text100"><tspan |
128 | 128 |
x="0 62.500019 125.00004" |
129 | 129 |
y="0" |
130 | 130 |
id="tspan98">ATA</tspan></text></g><g |
131 | 131 |
id="g102" |
132 |
- transform="matrix(0.24,0,0,0.24,655.3618,-159.6)"><text |
|
133 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
132 |
+ transform="matrix(0.24,0,0,0.24,655.3618,-207.76)"><text |
|
133 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
134 | 134 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
135 | 135 |
id="text106"><tspan |
136 | 136 |
x="0" |
137 | 137 |
y="0" |
138 | 138 |
id="tspan104">A</tspan></text></g><g |
139 | 139 |
id="g108" |
140 |
- transform="matrix(0.24,0,0,0.24,670.3618,-159.6)"><text |
|
141 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
140 |
+ transform="matrix(0.24,0,0,0.24,670.3618,-207.76)"><text |
|
141 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
142 | 142 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
143 | 143 |
id="text112"><tspan |
144 | 144 |
x="0 62.500019" |
145 | 145 |
y="0" |
146 | 146 |
id="tspan110">GG</tspan></text></g><g |
147 | 147 |
id="g114" |
148 |
- transform="matrix(0.24,0,0,0.24,700.3618,-159.6)"><text |
|
149 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
148 |
+ transform="matrix(0.24,0,0,0.24,700.3618,-207.76)"><text |
|
149 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
150 | 150 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
151 | 151 |
id="text118"><tspan |
152 | 152 |
x="0 62.500019 125.00004" |
153 | 153 |
y="0" |
154 | 154 |
id="tspan116">TTG</tspan></text></g><g |
155 | 155 |
id="g120" |
156 |
- transform="matrix(0.24,0,0,0.24,47.57834,-158.16)"><text |
|
157 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
156 |
+ transform="matrix(0.24,0,0,0.24,47.57897,-206.08)"><text |
|
157 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
158 | 158 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
159 | 159 |
id="text124"><tspan |
160 | 160 |
x="0 43.23 72.885002 90.089996 149.97 189.52499 214.53" |
161 | 161 |
y="0" |
162 | 162 |
id="tspan122">Azimuth</tspan></text></g><g |
163 | 163 |
id="g126" |
164 |
- transform="matrix(0.24,0,0,0.24,932.1604,-126.24)"><text |
|
165 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
164 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-177.28)"><text |
|
165 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
166 | 166 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
167 | 167 |
id="text130"><tspan |
168 | 168 |
x="0 38.017502 76.035004 114.9525" |
169 | 169 |
y="0" |
170 | 170 |
id="tspan128">23nt</tspan></text></g><g |
171 | 171 |
id="g132" |
172 |
- transform="matrix(0.24,0,0,0.24,932.1604,-159.84)"><text |
|
173 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
172 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-207.76)"><text |
|
173 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
174 | 174 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
175 | 175 |
id="text136"><tspan |
176 | 176 |
x="0 38.017502 76.035004 114.9525" |
177 | 177 |
y="0" |
178 | 178 |
id="tspan134">30nt</tspan></text></g><g |
179 | 179 |
id="g138" |
180 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,110.958)"><path |
|
180 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,77.7752)"><path |
|
181 | 181 |
d="M 0,0 1303020,1" |
182 | 182 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
183 | 183 |
id="path140" /></g><g |
184 | 184 |
id="g142" |
185 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,809.5659,110.958)"><path |
|
185 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,809.5659,77.7752)"><path |
|
186 | 186 |
d="M 0,0 1303020,1" |
187 | 187 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
188 | 188 |
id="path144" /></g><g |
189 | 189 |
id="g146" |
190 |
- transform="matrix(0.24,0,0,0.24,236.2206,-257.28)"><text |
|
191 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
190 |
+ transform="matrix(0.24,0,0,0.24,236.2206,-304.24)"><text |
|
191 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
192 | 192 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
193 | 193 |
id="text150"><tspan |
194 | 194 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015" |
195 | 195 |
y="0" |
196 | 196 |
id="tspan148">GTG…ACCT</tspan></text></g><g |
197 | 197 |
id="g152" |
198 |
- transform="matrix(0.24,0,0,0.24,356.2205,-257.28)"><text |
|
199 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
198 |
+ transform="matrix(0.24,0,0,0.24,356.2205,-304.24)"><text |
|
199 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
200 | 200 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
201 | 201 |
id="text156"><tspan |
202 | 202 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
203 | 203 |
y="0" |
204 | 204 |
id="tspan154">ATCGATGCTGATGCTA</tspan></text></g><g |
205 | 205 |
id="g158" |
206 |
- transform="matrix(0.24,0,0,0.24,596.2205,-257.28)"><text |
|
207 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
206 |
+ transform="matrix(0.24,0,0,0.24,596.2205,-304.24)"><text |
|
207 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
208 | 208 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
209 | 209 |
id="text162"><tspan |
210 | 210 |
x="0" |
211 | 211 |
y="0" |
212 | 212 |
id="tspan160">G</tspan></text></g><g |
213 | 213 |
id="g164" |
214 |
- transform="matrix(0.24,0,0,0.24,611.2205,-257.28)"><text |
|
215 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
214 |
+ transform="matrix(0.24,0,0,0.24,611.2205,-304.24)"><text |
|
215 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
216 | 216 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
217 | 217 |
id="text168"><tspan |
218 | 218 |
x="0 62.500019 125.00004" |
219 | 219 |
y="0" |
220 | 220 |
id="tspan166">ATA</tspan></text></g><g |
221 | 221 |
id="g170" |
222 |
- transform="matrix(0.24,0,0,0.24,656.2205,-257.28)"><text |
|
223 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
222 |
+ transform="matrix(0.24,0,0,0.24,656.2205,-304.24)"><text |
|
223 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
224 | 224 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
225 | 225 |
id="text174"><tspan |
226 | 226 |
x="0" |
227 | 227 |
y="0" |
228 | 228 |
id="tspan172">A</tspan></text></g><g |
229 | 229 |
id="g176" |
230 |
- transform="matrix(0.24,0,0,0.24,671.2205,-257.28)"><text |
|
231 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
230 |
+ transform="matrix(0.24,0,0,0.24,671.2205,-304.24)"><text |
|
231 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
232 | 232 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
233 | 233 |
id="text180"><tspan |
234 | 234 |
x="0 62.500019" |
235 | 235 |
y="0" |
236 | 236 |
id="tspan178">GG</tspan></text></g><g |
237 | 237 |
id="g182" |
238 |
- transform="matrix(0.24,0,0,0.24,701.2205,-257.28)"><text |
|
239 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
238 |
+ transform="matrix(0.24,0,0,0.24,701.2205,-304.24)"><text |
|
239 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
240 | 240 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
241 | 241 |
id="text186"><tspan |
242 | 242 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012" |
243 | 243 |
y="0" |
244 | 244 |
id="tspan184">TTG…ATT</tspan></text></g><g |
245 | 245 |
id="g188" |
246 |
- transform="matrix(0.24,0,0,0.24,64.70366,-256.32)"><text |
|
247 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
246 |
+ transform="matrix(0.24,0,0,0.24,64.70397,-303.28)"><text |
|
247 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
248 | 248 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
249 | 249 |
id="text192"><tspan |
250 | 250 |
x="0 31.77 48.990002 88.559998 128.13 165.60001" |
251 | 251 |
y="0" |
252 | 252 |
id="tspan190">Lindel</tspan></text></g><g |
253 | 253 |
id="g194" |
254 |
- transform="matrix(0.24,0,0,0.24,932.1607,-256.8)"><text |
|
255 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
254 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-304)"><text |
|
255 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
256 | 256 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
257 | 257 |
id="text198"><tspan |
258 | 258 |
x="0 38.017502 76.035004 114.9525" |
259 | 259 |
y="0" |
260 | 260 |
id="tspan196">65nt</tspan></text></g><g |
261 | 261 |
id="g200" |
262 |
- transform="matrix(0,7.874016e-5,7.874016e-5,0,702.8361,51.20459)"><path |
|
262 |
+ transform="matrix(0,7.874016e-5,7.874016e-5,0,702.8361,35.27654)"><path |
|
263 | 263 |
d="m 369332,1338398 c -101988.6,0 -184666.7,-13779 -184666.7,-30777 l 1.4,-596951.3 c 0,-16997.7 -82678.1,-30777 -184666.7,-30777 101988.6,0 184666.7,-13779.3 184666.7,-30777 V 30777.01 C 184666.7,13779.33 267344.8,0 369333.4,0" |
264 | 264 |
style="fill:none;stroke:#000000;stroke-width:6350;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
265 | 265 |
id="path202" /></g><g |
266 | 266 |
id="g204" |
267 |
- transform="matrix(0,7.874016e-5,7.874016e-5,0,239.6189,47.80407)"><path |
|
267 |
+ transform="matrix(0,7.874016e-5,7.874016e-5,0,239.6193,31.87602)"><path |
|
268 | 268 |
d="m 409377,1438850 c -113046.3,0 -204688.5,-15273 -204688.5,-34113 V 765034.2 c 0,-18840 -91642.2,-34112.9 -204688.5,-34112.9 113046.3,0 204688.5,-15272.9 204688.5,-34112.9 V 34112.89 C 204688.5,15272.86 296330.7,0 409377,0" |
269 | 269 |
style="fill:none;stroke:#000000;stroke-width:6350;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
270 | 270 |
id="path206" /></g><g |
271 | 271 |
id="g208" |
272 |
- transform="matrix(0,7.874016e-5,7.874016e-5,0,359.0259,46.94667)"><path |
|
272 |
+ transform="matrix(0,7.874016e-5,7.874016e-5,0,359.0263,31.01862)"><path |
|
273 | 273 |
d="m 409080.4,3715436 c -112964.5,0 -204540.2,-15261 -204540.2,-34087 V 1921495 c 0,-18826 -91575.8,-34087 -204540.2,-34087 112964.4,0 204540.2,-15261 204540.2,-34087 V 34086.6 C 204540.2,15261.09 296115.9,0 409080.4,0" |
274 | 274 |
style="fill:none;stroke:#000000;stroke-width:6350;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
275 | 275 |
id="path210" /></g><g |
276 | 276 |
id="g212" |
277 |
- transform="matrix(0,7.874016e-5,7.874016e-5,0,654.9509,51.76627)"><path |
|
277 |
+ transform="matrix(0,7.874016e-5,7.874016e-5,0,654.9512,35.83825)"><path |
|
278 | 278 |
d="m 330521,565346 c -91270.8,0 -165260.5,-12331 -165260.5,-27542.1 V 314732.2 c 0,-15211.1 -73989.64,-27542.1 -165260.5,-27542.1 91270.86,0 165260.5,-12331 165260.5,-27542.1 V 27542.07 C 165260.5,12331 239250.2,0 330521,0" |
279 | 279 |
style="fill:none;stroke:#000000;stroke-width:6350;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
280 | 280 |
id="path214" /></g><g |
281 | 281 |
id="g216" |
282 |
- transform="matrix(0.24,0,0,0.24,455.1106,-338.16)"><text |
|
283 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
282 |
+ transform="matrix(0.24,0,0,0.24,455.1106,-367.84)"><text |
|
283 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
284 | 284 |
style="font-variant:normal;font-weight:normal;font-size:83.3333px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
285 | 285 |
id="text220"><tspan |
286 | 286 |
x="0 38.541664 82.291664 122.39166 157.80833 199.47499 228.64166 247.39166 272.90833 315.09998 357.29166 400.26666 428.39166" |
287 | 287 |
y="0" |
288 | 288 |
id="tspan218">Spacer (20nt)</tspan></text></g><g |
289 | 289 |
id="g222" |
290 |
- transform="matrix(0.24,0,0,0.24,629.868,-338.16)"><text |
|
291 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
290 |
+ transform="matrix(0.24,0,0,0.24,629.8683,-367.84)"><text |
|
291 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
292 | 292 |
style="font-variant:normal;font-weight:normal;font-size:83.3333px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
293 | 293 |
id="text226"><tspan |
294 | 294 |
x="0 37.083332 85.5 156.83333 175.58333 201.08333 243.24998 286.25 314.41666" |
295 | 295 |
y="0" |
296 | 296 |
id="tspan224">PAM (3nt)</tspan></text></g><g |
297 | 297 |
id="g228" |
298 |
- transform="matrix(0.24,0,0,0.24,739.547,-338.16)"><text |
|
299 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
298 |
+ transform="matrix(0.24,0,0,0.24,739.5473,-367.84)"><text |
|
299 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
300 | 300 |
style="font-variant:normal;font-weight:normal;font-size:83.3333px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
301 | 301 |
id="text232"><tspan |
302 | 302 |
x="0 42.191666 84.383331 127.325" |
303 | 303 |
y="0" |
304 | 304 |
id="tspan230">29nt</tspan></text></g><g |
305 | 305 |
id="g234" |
306 |
- transform="matrix(0.24,0,0,0.24,272.1051,-338.16)"><text |
|
307 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
306 |
+ transform="matrix(0.24,0,0,0.24,272.1054,-367.84)"><text |
|
307 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
308 | 308 |
style="font-variant:normal;font-weight:normal;font-size:83.3333px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
309 | 309 |
id="text238"><tspan |
310 | 310 |
x="0 42.191666 84.383331 127.325" |
311 | 311 |
y="0" |
312 | 312 |
id="tspan236">13nt</tspan></text></g><g |
313 | 313 |
id="g240" |
314 |
- transform="matrix(0.24,0,0,0.24,355.1134,-93.35999)"><text |
|
315 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
314 |
+ transform="matrix(0.24,0,0,0.24,355.1134,-85.83999)"><text |
|
315 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
316 | 316 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
317 | 317 |
id="text244"><tspan |
318 | 318 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
319 | 319 |
y="0" |
320 | 320 |
id="tspan242">ATCGATGCTGATGCTA</tspan></text></g><g |
321 | 321 |
id="g246" |
322 |
- transform="matrix(0.24,0,0,0.24,595.1134,-93.35999)"><text |
|
323 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
322 |
+ transform="matrix(0.24,0,0,0.24,595.1134,-85.83999)"><text |
|
323 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
324 | 324 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
325 | 325 |
id="text250"><tspan |
326 | 326 |
x="0" |
327 | 327 |
y="0" |
328 | 328 |
id="tspan248">G</tspan></text></g><g |
329 | 329 |
id="g252" |
330 |
- transform="matrix(0.24,0,0,0.24,610.1134,-93.35999)"><text |
|
331 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
330 |
+ transform="matrix(0.24,0,0,0.24,610.1134,-85.83999)"><text |
|
331 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
332 | 332 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
333 | 333 |
id="text256"><tspan |
334 | 334 |
x="0 62.500019 125.00004" |
335 | 335 |
y="0" |
336 | 336 |
id="tspan254">ATA</tspan></text></g><g |
337 | 337 |
id="g258" |
338 |
- transform="matrix(0.24,0,0,0.24,655.1134,-93.35999)"><text |
|
339 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
338 |
+ transform="matrix(0.24,0,0,0.24,655.1134,-85.83999)"><text |
|
339 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
340 | 340 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
341 | 341 |
id="text262"><tspan |
342 | 342 |
x="0" |
343 | 343 |
y="0" |
344 | 344 |
id="tspan260">A</tspan></text></g><g |
345 | 345 |
id="g264" |
346 |
- transform="matrix(0.24,0,0,0.24,670.1134,-93.35999)"><text |
|
347 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
346 |
+ transform="matrix(0.24,0,0,0.24,670.1134,-85.83999)"><text |
|
347 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
348 | 348 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
349 | 349 |
id="text268"><tspan |
350 | 350 |
x="0 62.500019" |
351 | 351 |
y="0" |
352 | 352 |
id="tspan266">GG</tspan></text></g><g |
353 | 353 |
id="g270" |
354 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.421,273.3188)"><path |
|
354 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4211,294.7755)"><path |
|
355 | 355 |
d="M 0,0 2769397,1" |
356 | 356 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
357 | 357 |
id="path272" /></g><g |
358 | 358 |
id="g274" |
359 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,707.01,273.3188)"><path |
|
359 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,707.0102,294.7755)"><path |
|
360 | 360 |
d="M 0,0 2605485,1" |
361 | 361 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
362 | 362 |
id="path276" /></g><path |
363 |
- d="m 664.6969,289.9535 v 24.5632 h -2.25 v -24.5632 z m 2.25,23.4382 -3.375,6.75 -3.375,-6.75 z" |
|
363 |
+ d="m 664.6969,311.4101 v 24.5632 h -2.25 v -24.5632 z m 2.25,23.4382 -3.375,6.75 -3.375,-6.7499 z" |
|
364 | 364 |
style="fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
365 | 365 |
id="path278" /><g |
366 | 366 |
id="g280" |
367 |
- transform="matrix(0.24,0,0,0.24,629.8672,-32.87999)"><text |
|
368 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
367 |
+ transform="matrix(0.24,0,0,0.24,629.8672,-25.35999)"><text |
|
368 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
369 | 369 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
370 | 370 |
id="text284"><tspan |
371 | 371 |
x="0 33.022499 76.245003 140.3175 157.515 186.71249 203.91 228.0825" |
372 | 372 |
y="0" |
373 | 373 |
id="tspan282">PAM site</tspan></text></g><g |
374 | 374 |
id="g286" |
375 |
- transform="matrix(0.24,0,0,0.24,545.9901,-32.87999)"><text |
|
376 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
375 |
+ transform="matrix(0.24,0,0,0.24,545.9902,-25.35999)"><text |
|
376 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
377 | 377 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
378 | 378 |
id="text290"><tspan |
379 | 379 |
x="0 40.102501 79.68 104.7075 121.935 151.08749 168.24001 192.4425" |
380 | 380 |
y="0" |
381 | 381 |
id="tspan288">Cut site</tspan></text></g><path |
382 |
- d="m 599.3637,288.7615 -12.8872,23.3899 1.9707,1.0858 12.8872,-23.3899 z m -14.315,21.3187 -0.3013,7.5407 6.2134,-4.2833 z" |
|
382 |
+ d="m 599.3638,310.2182 -12.8872,23.3899 1.9707,1.0858 12.8872,-23.3899 z m -14.315,21.3187 -0.3013,7.5407 6.2134,-4.2833 z" |
|
383 | 383 |
style="fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
384 | 384 |
id="path292" /><g |
385 | 385 |
id="g294" |
386 |
- transform="matrix(0.24,0,0,0.24,9.549605,-88.79999)"><text |
|
387 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
386 |
+ transform="matrix(0.24,0,0,0.24,9.549605,-81.27999)"><text |
|
387 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
388 | 388 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
389 | 389 |
id="text298"><tspan |
390 | 390 |
x="0 22.92 61.439999 86.235001 125.805 150.075 189.645 218.78999 258.35999 294.32999 326.10001 363.57001 389.64001" |
391 | 391 |
y="0" |
392 | 392 |
id="tspan296">(Protospacer)</tspan></text></g><g |
393 | 393 |
id="g300" |
394 |
- transform="matrix(0.24,0,0,0.24,342.6961,-77.27999)"><text |
|
395 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
394 |
+ transform="matrix(0.24,0,0,0.24,342.6961,-69.75999)"><text |
|
395 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
396 | 396 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
397 | 397 |
id="text304"><tspan |
398 | 398 |
x="0 38.017502" |
399 | 399 |
y="0" |
400 | 400 |
id="tspan302">5’</tspan></text></g><g |
401 | 401 |
id="g306" |
402 |
- transform="matrix(0.24,0,0,0.24,706.6087,-77.27999)"><text |
|
403 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
402 |
+ transform="matrix(0.24,0,0,0.24,706.6088,-69.75999)"><text |
|
403 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
404 | 404 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
405 | 405 |
id="text310"><tspan |
406 | 406 |
x="0 38.017502" |
407 | 407 |
y="0" |
408 | 408 |
id="tspan308">3’</tspan></text></g><g |
409 | 409 |
id="g312" |
410 |
- transform="matrix(0.24,0,0,0.24,932.1603,-92.39999)"><text |
|
411 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
410 |
+ transform="matrix(0.24,0,0,0.24,932.1604,-84.87999)"><text |
|
411 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
412 | 412 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
413 | 413 |
id="text316"><tspan |
414 | 414 |
x="0 38.017502 76.035004 114.9525" |
415 | 415 |
y="0" |
416 | 416 |
id="tspan314">23nt</tspan></text></g><g |
417 | 417 |
id="g318" |
418 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,177.7298)"><path |
|
418 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,143.5328)"><path |
|
419 | 419 |
d="M 0,0 2054114,1" |
420 | 420 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
421 | 421 |
id="path320" /></g><g |
422 | 422 |
id="g322" |
423 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,755.3,177.7298)"><path |
|
423 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,755.3003,143.5328)"><path |
|
424 | 424 |
d="M 0,0 1992203,1" |
425 | 425 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
426 | 426 |
id="path324" /></g><g |
427 | 427 |
id="g326" |
428 |
- transform="matrix(0.24,0,0,0.24,295.3618,-189.36)"><text |
|
429 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
428 |
+ transform="matrix(0.24,0,0,0.24,295.3618,-237.52)"><text |
|
429 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
430 | 430 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
431 | 431 |
id="text330"><tspan |
432 | 432 |
x="0 62.500019 125.00004 187.50006" |
433 | 433 |
y="0" |
434 | 434 |
id="tspan328">ACCT</tspan></text></g><g |
435 | 435 |
id="g332" |
436 |
- transform="matrix(0.24,0,0,0.24,355.3618,-189.36)"><text |
|
437 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
436 |
+ transform="matrix(0.24,0,0,0.24,355.3618,-237.52)"><text |
|
437 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
438 | 438 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
439 | 439 |
id="text336"><tspan |
440 | 440 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
441 | 441 |
y="0" |
442 | 442 |
id="tspan334">ATCGATGCTGATGCTA</tspan></text></g><g |
443 | 443 |
id="g338" |
444 |
- transform="matrix(0.24,0,0,0.24,595.3618,-189.36)"><text |
|
445 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
444 |
+ transform="matrix(0.24,0,0,0.24,595.3618,-237.52)"><text |
|
445 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
446 | 446 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
447 | 447 |
id="text342"><tspan |
448 | 448 |
x="0" |
449 | 449 |
y="0" |
450 | 450 |
id="tspan340">G</tspan></text></g><g |
451 | 451 |
id="g344" |
452 |
- transform="matrix(0.24,0,0,0.24,610.3618,-189.36)"><text |
|
453 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
452 |
+ transform="matrix(0.24,0,0,0.24,610.3618,-237.52)"><text |
|
453 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
454 | 454 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
455 | 455 |
id="text348"><tspan |
456 | 456 |
x="0 62.500019 125.00004" |
457 | 457 |
y="0" |
458 | 458 |
id="tspan346">ATA</tspan></text></g><g |
459 | 459 |
id="g350" |
460 |
- transform="matrix(0.24,0,0,0.24,655.3618,-189.36)"><text |
|
461 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
460 |
+ transform="matrix(0.24,0,0,0.24,655.3618,-237.52)"><text |
|
461 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
462 | 462 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
463 | 463 |
id="text354"><tspan |
464 | 464 |
x="0" |
465 | 465 |
y="0" |
466 | 466 |
id="tspan352">A</tspan></text></g><g |
467 | 467 |
id="g356" |
468 |
- transform="matrix(0.24,0,0,0.24,670.3618,-189.36)"><text |
|
469 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
468 |
+ transform="matrix(0.24,0,0,0.24,670.3618,-237.52)"><text |
|
469 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
470 | 470 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
471 | 471 |
id="text360"><tspan |
472 | 472 |
x="0 62.500019" |
473 | 473 |
y="0" |
474 | 474 |
id="tspan358">GG</tspan></text></g><g |
475 | 475 |
id="g362" |
476 |
- transform="matrix(0.24,0,0,0.24,700.3618,-189.36)"><text |
|
477 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
476 |
+ transform="matrix(0.24,0,0,0.24,700.3618,-237.52)"><text |
|
477 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
478 | 478 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
479 | 479 |
id="text366"><tspan |
480 | 480 |
x="0 62.500019 125.00004" |
481 | 481 |
y="0" |
482 | 482 |
id="tspan364">TTG</tspan></text></g><g |
483 | 483 |
id="g368" |
484 |
- transform="matrix(0.24,0,0,0.24,43.92335,-187.92)"><text |
|
485 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
484 |
+ transform="matrix(0.24,0,0,0.24,43.92398,-236.08)"><text |
|
485 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
486 | 486 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
487 | 487 |
id="text372"><tspan |
488 | 488 |
x="0 40.627499 80.205002 97.432503 134.91 169.3125 206.41499 231.4425" |
489 | 489 |
y="0" |
490 | 490 |
id="tspan370">RuleSet1</tspan></text></g><g |
491 | 491 |
id="g374" |
492 |
- transform="matrix(0.24,0,0,0.24,932.1604,-189.6)"><text |
|
493 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
492 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-237.76)"><text |
|
493 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
494 | 494 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
495 | 495 |
id="text378"><tspan |
496 | 496 |
x="0 38.017502 76.035004 114.9525" |
497 | 497 |
y="0" |
498 | 498 |
id="tspan376">30nt</tspan></text></g><g |
499 | 499 |
id="g380" |
500 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,145.6336)"><path |
|
500 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.4206,111.4367)"><path |
|
501 | 501 |
d="M 0,0 1758754,1" |
502 | 502 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
503 | 503 |
id="path382" /></g><g |
504 | 504 |
id="g384" |
505 |
- transform="matrix(7.874016e-5,0,0,-7.874016e-5,792.8055,145.6336)"><path |
|
505 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,792.8058,111.4367)"><path |
|
506 | 506 |
d="M 0,0 1515883,1" |
507 | 507 |
style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
508 | 508 |
id="path386" /></g><g |
509 | 509 |
id="g388" |
510 |
- transform="matrix(0.24,0,0,0.24,266.6859,-221.52)"><text |
|
511 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
510 |
+ transform="matrix(0.24,0,0,0.24,266.6859,-269.68)"><text |
|
511 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
512 | 512 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
513 | 513 |
id="text392"><tspan |
514 | 514 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009" |
515 | 515 |
y="0" |
516 | 516 |
id="tspan390">AAACCT</tspan></text></g><g |
517 | 517 |
id="g394" |
518 |
- transform="matrix(0.24,0,0,0.24,356.6859,-221.52)"><text |
|
519 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
518 |
+ transform="matrix(0.24,0,0,0.24,356.6859,-269.68)"><text |
|
519 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
520 | 520 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
521 | 521 |
id="text398"><tspan |
522 | 522 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
523 | 523 |
y="0" |
524 | 524 |
id="tspan396">ATCGATGCTGATGCTA</tspan></text></g><g |
525 | 525 |
id="g400" |
526 |
- transform="matrix(0.24,0,0,0.24,596.6859,-221.52)"><text |
|
527 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
526 |
+ transform="matrix(0.24,0,0,0.24,596.6859,-269.68)"><text |
|
527 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
528 | 528 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
529 | 529 |
id="text404"><tspan |
530 | 530 |
x="0" |
531 | 531 |
y="0" |
532 | 532 |
id="tspan402">G</tspan></text></g><g |
533 | 533 |
id="g406" |
534 |
- transform="matrix(0.24,0,0,0.24,611.6859,-221.52)"><text |
|
535 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
534 |
+ transform="matrix(0.24,0,0,0.24,611.6859,-269.68)"><text |
|
535 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
536 | 536 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
537 | 537 |
id="text410"><tspan |
538 | 538 |
x="0 62.500019 125.00004" |
539 | 539 |
y="0" |
540 | 540 |
id="tspan408">ATA</tspan></text></g><g |
541 | 541 |
id="g412" |
542 |
- transform="matrix(0.24,0,0,0.24,656.6859,-221.52)"><text |
|
543 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
542 |
+ transform="matrix(0.24,0,0,0.24,656.6859,-269.68)"><text |
|
543 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
544 | 544 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
545 | 545 |
id="text416"><tspan |
546 | 546 |
x="0" |
547 | 547 |
y="0" |
548 | 548 |
id="tspan414">A</tspan></text></g><g |
549 | 549 |
id="g418" |
550 |
- transform="matrix(0.24,0,0,0.24,671.6859,-221.52)"><text |
|
551 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
550 |
+ transform="matrix(0.24,0,0,0.24,671.6859,-269.68)"><text |
|
551 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
552 | 552 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
553 | 553 |
id="text422"><tspan |
554 | 554 |
x="0 62.500019" |
555 | 555 |
y="0" |
556 | 556 |
id="tspan420">GG</tspan></text></g><g |
557 | 557 |
id="g424" |
558 |
- transform="matrix(0.24,0,0,0.24,701.6859,-221.52)"><text |
|
559 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
558 |
+ transform="matrix(0.24,0,0,0.24,701.6859,-269.68)"><text |
|
559 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
560 | 560 |
style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#a9d18e;fill-opacity:1;fill-rule:nonzero;stroke:none" |
561 | 561 |
id="text428"><tspan |
562 | 562 |
x="0 62.500019 125.00004 187.50006 250.00008 312.50009" |
563 | 563 |
y="0" |
564 | 564 |
id="tspan426">TTGGGC</tspan></text></g><g |
565 | 565 |
id="g430" |
566 |
- transform="matrix(0.24,0,0,0.24,24.85968,-219.84)"><text |
|
567 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
566 |
+ transform="matrix(0.24,0,0,0.24,24.85968,-268)"><text |
|
567 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
568 | 568 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
569 | 569 |
id="text434"><tspan |
570 | 570 |
x="0 40.102501 80.730003 99.457497 133.86 172.3875 213.015 242.1675 273.345 309.2475" |
571 | 571 |
y="0" |
572 | 572 |
id="tspan432">CRISPRscan</tspan></text></g><g |
573 | 573 |
id="g436" |
574 |
- transform="matrix(0.24,0,0,0.24,932.1604,-221.76)"><text |
|
575 |
- transform="matrix(1,0,0,-1,0,1500)" |
|
574 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-269.68)"><text |
|
575 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
576 | 576 |
style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
577 | 577 |
id="text440"><tspan |
578 | 578 |
x="0 38.017502 76.035004 114.9525" |
579 | 579 |
y="0" |
580 |
- id="tspan438">35nt</tspan></text></g></g></g></svg> |
|
580 |
+ id="tspan438">35nt</tspan></text></g><g |
|
581 |
+ id="g442" |
|
582 |
+ transform="matrix(0.24,0,0,0.24,354.9446,-146.8)"><text |
|
583 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
584 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
585 |
+ id="text446"><tspan |
|
586 |
+ x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031 937.50031" |
|
587 |
+ y="0" |
|
588 |
+ id="tspan444">ATCGATGCTGATGCTA</tspan></text></g><g |
|
589 |
+ id="g448" |
|
590 |
+ transform="matrix(0.24,0,0,0.24,594.9446,-146.8)"><text |
|
591 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
592 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
593 |
+ id="text452"><tspan |
|
594 |
+ x="0" |
|
595 |
+ y="0" |
|
596 |
+ id="tspan450">G</tspan></text></g><g |
|
597 |
+ id="g454" |
|
598 |
+ transform="matrix(0.24,0,0,0.24,609.9446,-146.8)"><text |
|
599 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
600 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
601 |
+ id="text458"><tspan |
|
602 |
+ x="0 62.500019 125.00004" |
|
603 |
+ y="0" |
|
604 |
+ id="tspan456">ATA</tspan></text></g><g |
|
605 |
+ id="g460" |
|
606 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,126.2522,234.0017)"><path |
|
607 |
+ d="M 0,0 2785439,1" |
|
608 |
+ style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
|
609 |
+ id="path462" /></g><g |
|
610 |
+ id="g464" |
|
611 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,663.5721,234.0017)"><path |
|
612 |
+ d="M 0,0 3155003,1" |
|
613 |
+ style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
|
614 |
+ id="path466" /></g><g |
|
615 |
+ id="g468" |
|
616 |
+ transform="matrix(0.24,0,0,0.24,27.76953,-143.92)"><text |
|
617 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
618 |
+ style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
619 |
+ id="text472"><tspan |
|
620 |
+ x="0 40.102501 80.730003 99.457497 133.86 172.3875 213.015 248.24249 272.44501 309.92249" |
|
621 |
+ y="0" |
|
622 |
+ id="tspan470">CRISPRater</tspan></text></g><g |
|
623 |
+ id="g474" |
|
624 |
+ transform="matrix(0.24,0,0,0.24,931.9916,-146.8)"><text |
|
625 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
626 |
+ style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
627 |
+ id="text478"><tspan |
|
628 |
+ x="0 38.017502 76.035004 114.9525" |
|
629 |
+ y="0" |
|
630 |
+ id="tspan476">20nt</tspan></text></g><g |
|
631 |
+ id="g480" |
|
632 |
+ transform="matrix(0.24,0,0,0.24,369.6331,-116.32)"><text |
|
633 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
634 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
635 |
+ id="text484"><tspan |
|
636 |
+ x="0 62.500019 125.00004 187.50006 250.00008 312.50009 375.00012 437.50015 500.00015 562.50018 625.00018 687.50024 750.00024 812.50024 875.00031" |
|
637 |
+ y="0" |
|
638 |
+ id="tspan482">TCGATGCTGATGCTA</tspan></text></g><g |
|
639 |
+ id="g486" |
|
640 |
+ transform="matrix(0.24,0,0,0.24,594.633,-116.32)"><text |
|
641 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
642 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
643 |
+ id="text490"><tspan |
|
644 |
+ x="0" |
|
645 |
+ y="0" |
|
646 |
+ id="tspan488">G</tspan></text></g><g |
|
647 |
+ id="g492" |
|
648 |
+ transform="matrix(0.24,0,0,0.24,609.633,-116.32)"><text |
|
649 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
650 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ffd966;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
651 |
+ id="text496"><tspan |
|
652 |
+ x="0 62.500019 125.00004" |
|
653 |
+ y="0" |
|
654 |
+ id="tspan494">ATA</tspan></text></g><g |
|
655 |
+ id="g498" |
|
656 |
+ transform="matrix(0.24,0,0,0.24,654.633,-116.32)"><text |
|
657 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
658 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#ff0000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
659 |
+ id="text502"><tspan |
|
660 |
+ x="0" |
|
661 |
+ y="0" |
|
662 |
+ id="tspan500">A</tspan></text></g><g |
|
663 |
+ id="g504" |
|
664 |
+ transform="matrix(0.24,0,0,0.24,669.633,-116.32)"><text |
|
665 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
666 |
+ style="font-variant:normal;font-weight:normal;font-size:104.167px;font-family:Courier;-inkscape-font-specification:Courier;writing-mode:lr-tb;fill:#c55a11;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
667 |
+ id="text508"><tspan |
|
668 |
+ x="0 62.500019" |
|
669 |
+ y="0" |
|
670 |
+ id="tspan506">GG</tspan></text></g><g |
|
671 |
+ id="g510" |
|
672 |
+ transform="matrix(7.874016e-5,0,0,7.874016e-5,125.9409,264.4457)"><path |
|
673 |
+ d="M 0,0 2972553,1315" |
|
674 |
+ style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
|
675 |
+ id="path512" /></g><g |
|
676 |
+ id="g514" |
|
677 |
+ transform="matrix(7.874016e-5,0,0,-7.874016e-5,709.0563,264.4458)"><path |
|
678 |
+ d="M 0,0 2573401,1" |
|
679 |
+ style="fill:none;stroke:#000000;stroke-width:22225;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:8;stroke-dasharray:none;stroke-opacity:1" |
|
680 |
+ id="path516" /></g><g |
|
681 |
+ id="g518" |
|
682 |
+ transform="matrix(0.24,0,0,0.24,44.70398,-113.44)"><text |
|
683 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
684 |
+ style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
685 |
+ id="text522"><tspan |
|
686 |
+ x="0 40.102501 80.730003 99.457497 133.86 172.3875 213.015 248.9175" |
|
687 |
+ y="0" |
|
688 |
+ id="tspan520">CRISPRai</tspan></text></g><g |
|
689 |
+ id="g524" |
|
690 |
+ transform="matrix(0.24,0,0,0.24,931.6803,-112)"><text |
|
691 |
+ transform="matrix(1,0,0,-1,0,1558)" |
|
692 |
+ style="font-variant:normal;font-weight:normal;font-size:75px;font-family:Calibri;-inkscape-font-specification:Calibri;writing-mode:lr-tb;fill:#000000;fill-opacity:1;fill-rule:nonzero;stroke:none" |
|
693 |
+ id="text528"><tspan |
|
694 |
+ x="0 38.017502 76.035004 114.9525" |
|
695 |
+ y="0" |
|
696 |
+ id="tspan526">22nt</tspan></text></g></g></g></svg> |
... | ... |
@@ -1,3 +1,34 @@ |
1 |
+@article{crisprai, |
|
2 |
+ title={Compact and highly active next-generation libraries for CRISPR-mediated gene repression and activation}, |
|
3 |
+ author={Horlbeck, Max A and Gilbert, Luke A and Villalta, Jacqueline E and Adamson, Britt and Pak, Ryan A and Chen, Yuwen and Fields, Alexander P and Park, Chong Yon and Corn, Jacob E and Kampmann, Martin and others}, |
|
4 |
+ journal={elife}, |
|
5 |
+ volume={5}, |
|
6 |
+ year={2016}, |
|
7 |
+ publisher={eLife Sciences Publications, Ltd} |
|
8 |
+} |
|
9 |
+ |
|
10 |
+@article{casrxrf, |
|
11 |
+ title={Massively parallel Cas13 screens reveal principles for guide RNA design}, |
|
12 |
+ author={Wessels, Hans-Hermann and M{\'e}ndez-Mancilla, Alejandro and Guo, Xinyi and Legut, Mateusz and Daniloski, Zharko and Sanjana, Neville E}, |
|
13 |
+ journal={Nature biotechnology}, |
|
14 |
+ volume={38}, |
|
15 |
+ number={6}, |
|
16 |
+ pages={722--727}, |
|
17 |
+ year={2020}, |
|
18 |
+ publisher={Nature Publishing Group} |
|
19 |
+} |
|
20 |
+ |
|
21 |
+@article{crisprater, |
|
22 |
+ title={Refined sgRNA efficacy prediction improves large-and small-scale CRISPR--Cas9 applications}, |
|
23 |
+ author={Labuhn, Maurice and Adams, Felix F and Ng, Michelle and Knoess, Sabine and Schambach, Axel and Charpentier, Emmanuelle M and Schwarzer, Adrian and Mateo, Juan L and Klusmann, Jan-Henning and Heckl, Dirk}, |
|
24 |
+ journal={Nucleic acids research}, |
|
25 |
+ volume={46}, |
|
26 |
+ number={3}, |
|
27 |
+ pages={1375--1385}, |
|
28 |
+ year={2018}, |
|
29 |
+ publisher={Oxford University Press} |
|
30 |
+} |
|
31 |
+ |
|
1 | 32 |
@article{crisprscan, |
2 | 33 |
title={CRISPRscan: designing highly efficient sgRNAs for CRISPR-Cas9 targeting in vivo}, |
3 | 34 |
author={Moreno-Mateos, Miguel A and Vejnar, Charles E and Beaudoin, Jean-Denis and Fernandez, Juan P and Mis, Emily K and Khokha, Mustafa K and Giraldez, Antonio J}, |