tilling sgRNA library design
1
@renxj2008-12842
Last seen 7.6 years ago
Hi,
I found the CRISPRseek is a good platform to design the sgRNA. Is there someone try to use it design the tilling paired sgRNA? If who know how to design the paired tilling sgRNA, please tell me at xingjie.ren@ucsf.edu.
Thanks very much!
Best,
xingjie
bioconductor
crisprseek
• 1.0k views
@julie-zhu-3596
Last seen 12 months ago
United States
Xingjie,
What is the goal of your study?
Do you need to filter gRNAs using off target score or gRNA efficacy?
To obtain all the gRNAs for a given genome without any filtering criteria, you can use the following script. Please change the genome, directory and library location accordingly.
Best regards,
Julie
######### gRNAsearch-wholeGenHg38.R
library(CRISPRseek)
library(BSgenome.Hsapiens.UCSC.hg38.masked)
args=commandArgs(trailingOnly = TRUE)
setwd("~/project/NAD/hg38")
chrom <- args[1]
batch.ind <- as.numeric(args[2])
chrom.size <- length(Hsapiens[[chrom]])
#### batch.ind 0 - 4
######### search in main chromosome only ########
gRNAPlusPAM.size <- 23
max.b <- ceiling(chrom.size / 1000000)
extra.bases2search <- (gRNAPlusPAM.size - 1) * (max.b - 1)
##### run in 5 jobs
max.b <- ceiling((chrom.size + extra.bases2search) / 1000000)
batch.start.bin <- min(batch.ind * ceiling(max.b/5), max.b)
batch.end.bin <- min(batch.start.bin + ceiling(max.b/5) - 1 , max.b)
for (i in batch.start.bin:batch.end.bin)
{
start <- min(i * 1000000 + 1 - i * (gRNAPlusPAM.size - 1), chrom.size)
end <- min(start + 1000000 - 1 , chrom.size)
if(i == max.b)
end <- chrom.size
inputFilePath <- DNAStringSet(substr(Hsapiens[[chrom]], start, end))
names(inputFilePath) <- paste(chrom, start, end, sep = "-")
outputDir <- paste("hg38gRNAs", chrom, "_", start, "_", end, sep = "")
print(inputFilePath)
flag <- TRUE
tryCatch(results <- offTargetAnalysis(inputFilePath,
findgRNAsWithREcutOnly = FALSE,
findPairedgRNAOnly = FALSE,
annotateExon = FALSE, fetchSequence = FALSE,
annotatePaired = FALSE, gRNAoutputName = "hg38",
findgRNAs = TRUE,exportAllgRNAs = "fasta",
enable.multicore = TRUE, n.cores.max = 20,
BSgenomeName = Hsapiens, chromToSearch = "",
max.mismatch = 0,
PAM.pattern = "NGG$",
outputDir = outputDir, overwrite = TRUE),
error=function(e) flag<<-FALSE)
if (!flag) next
}
}
Here is the batch script for running with bsub. Please change the genome, directory and library location accordingly.
for chrom in chr1 chr2 chr3 chr4 chr5 chr6 chr7 chr8 chr9 chr10 chr11 chr12 chr13 chr14 chr15 chr16 chr17 chr18 ch
r19 chr20 chr21 chr22 chrX chrY; do
for FILE in $(seq 0 4); do
SHF=seq-${chrom}-${FILE}.bsub
echo "#!/bin/bash" > $SHF
echo "#BSUB -P $FILE" >>$SHF
echo "workingDir=/project/CRISPRseek" >>$SHF
echo "export R_LIBS=/project/umw_mccb/R/R-3.3.1/lib64/R/library:/share/pkg/R/3.3.1/lib64/R/library
:/home/jz57w/R/x86_64-pc-linux-gnu-library/3.3" >>$SHF
workingDir=/project/CRISPRseek/hg38
echo "cd $workingDir" >>$SHF
echo "#BSUB -q long" >> $SHF
echo "#BSUB -R rusage[mem=20000]" >> $SHF
echo "#BSUB -W 240:00" >>$SHF
echo "#BSUB -o out.${chrom}.${FILE}.log" >>$SHF
echo "#BSUB -e err.${chrom}.${FILE}.log" >>$SHF
echo "/project/umw_mccb/bin/R CMD BATCH --no-save --no-restore '--args $chrom $FILE' /project/CRISPRseek/hg38/gRNAsearch-wholeGenHg38.R $SHF.log" >> $SHF
bsub < $SHF
sleep 5
done
Done
Best,
Julie
From: "renxj2008 [bioc]" <noreply@bioconductor.org<mailto:noreply@bioconductor.org>>
Reply-To: "reply+6d139c94+code@bioconductor.org<mailto:reply+6d139c94+code@bioconductor.org>" <reply+6d139c94+code@bioconductor.org<mailto:reply+6d139c94+code@bioconductor.org>>
Date: Friday, April 14, 2017 1:37 AM
To: Lihua Julie Zhu <julie.zhu@umassmed.edu<mailto:julie.zhu@umassmed.edu>>
Subject: [bioc] tilling sgRNA library design
Activity on a post you are following on support.bioconductor.org<https: support.bioconductor.org="">
User renxj2008<https: support.bioconductor.org="" u="" 12842=""/> wrote Question: tilling sgRNA library design<https: support.bioconductor.org="" p="" 94964=""/>:
Hi,
I found the CRISPRseek is a good platform to design the sgRNA. Is there someone try to use it design the tilling sgRNA? If who know how to design the tilling sgRNA, please tell me at xingjie.ren@ucsf.edu<mailto:xingjie.ren@ucsf.edu>.
Thanks very much!
Best,
xingjie
________________________________
Post tags: bioconductor, crisprseek
You may reply via email or visit
tilling sgRNA library design
Login before adding your answer.
Traffic: 539 users visited in the last hour