Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- fetchSeq :: BioSeq DNA a => Genome -> BED -> IO (Either String (DNA a))
- clipBed :: (BEDLike b, Monad m) => [(ByteString, Int)] -> ConduitT b b m ()
- data CutoffMotif = CutoffMotif {
- _motif_name :: ByteString
- _motif_pwm :: PWM
- _motif_sigma :: Vector Double
- _motif_pwm_rc :: PWM
- _motif_sigma_rc :: Vector Double
- _background :: Bkgd
- _cutoff :: Double
- _cdf :: CDF
- mkCutoffMotif :: Bkgd -> Double -> Motif -> CutoffMotif
- scanMotif :: (BEDLike b, MonadIO m) => Genome -> [CutoffMotif] -> ConduitT b BED m ()
- monoColonalize :: Monad m => ConduitT BED BED m ()
- newtype BaseMap = BaseMap (HashMap ByteString BitVector)
- baseMap :: PrimMonad m => [(ByteString, Int)] -> ConduitT BED o m BaseMap
- queryBaseMap :: BEDLike b => b -> BaseMap -> Maybe [Bool]
- rpkmBed :: (PrimMonad m, BEDLike b, Vector v Double) => [b] -> ConduitT BED o m (v Double)
- rpkmSortedBed :: (PrimMonad m, BEDLike b, Vector v Double) => Sorted (Vector b) -> ConduitT BED o m (v Double)
- countTagsBed :: (PrimMonad m, BEDLike b, Vector v Int) => [b] -> ConduitT BED o m (v Int, Int)
- countTagsBinBed :: (Integral a, PrimMonad m, Vector v a, BEDLike b) => Int -> [b] -> ConduitT BED o m ([v a], Int)
- countTagsBinBed' :: (Integral a, PrimMonad m, Vector v a, BEDLike b1, BEDLike b2) => Int -> [b1] -> ConduitT b2 o m ([v a], Int)
- tagCountDistr :: PrimMonad m => Vector v Int => ConduitT BED o m (v Int)
- peakCluster :: (BEDLike b, Monad m) => [b] -> Int -> Int -> ConduitT o BED m ()
Documentation
data CutoffMotif Source #
Motif with predefined cutoff score. All necessary intermediate data structure for motif scanning are stored.
CutoffMotif | |
|
:: Bkgd | |
-> Double | p-value |
-> Motif | |
-> CutoffMotif |
scanMotif :: (BEDLike b, MonadIO m) => Genome -> [CutoffMotif] -> ConduitT b BED m () Source #
Motif score is in [0, 1000]: ( 1 / (1 + exp (-(-logP - 5))) ) * 1000.
monoColonalize :: Monad m => ConduitT BED BED m () Source #
process a sorted BED stream, keep only mono-colonal tags
Count the tags (starting positions) at each position in the genome.
rpkmBed :: (PrimMonad m, BEDLike b, Vector v Double) => [b] -> ConduitT BED o m (v Double) Source #
calculate RPKM on a set of unique regions. Regions (in bed format) would be kept in memory but not tag file. RPKM: Readcounts per kilobase per million reads. Only counts the starts of tags
rpkmSortedBed :: (PrimMonad m, BEDLike b, Vector v Double) => Sorted (Vector b) -> ConduitT BED o m (v Double) Source #
calculate RPKM on a set of regions. Regions must be sorted. The Sorted data type is used to remind users to sort their data.
countTagsBed :: (PrimMonad m, BEDLike b, Vector v Int) => [b] -> ConduitT BED o m (v Int, Int) Source #
:: (Integral a, PrimMonad m, Vector v a, BEDLike b) | |
=> Int | bin size |
-> [b] | regions |
-> ConduitT BED o m ([v a], Int) |
divide each region into consecutive bins, and count tags for each bin and return the number of all tags. Note: a tag is considered to be overlapped with a region only if the starting position of the tag is in the region. For the common sense overlapping, use countTagsBinBed'.