module SequenceFormats.Genomic where import SequenceFormats.Bed (BedEntry (..), filterThroughBed) import SequenceFormats.Eigenstrat (EigenstratSnpEntry (..)) import SequenceFormats.FreqSum (FreqSumEntry (..)) import SequenceFormats.Pileup (PileupRow (..)) import SequenceFormats.Utils (Chrom) import SequenceFormats.VCF (VCFentry (..)) import Pipes (Producer) class Genomic a where genomicPosition :: a -> (Chrom, Int) genomicChrom :: a -> Chrom genomicChrom = (Chrom, Int) -> Chrom forall a b. (a, b) -> a fst ((Chrom, Int) -> Chrom) -> (a -> (Chrom, Int)) -> a -> Chrom forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> (Chrom, Int) forall a. Genomic a => a -> (Chrom, Int) genomicPosition genomicBase :: a -> Int genomicBase = (Chrom, Int) -> Int forall a b. (a, b) -> b snd ((Chrom, Int) -> Int) -> (a -> (Chrom, Int)) -> a -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> (Chrom, Int) forall a. Genomic a => a -> (Chrom, Int) genomicPosition instance Genomic EigenstratSnpEntry where genomicPosition :: EigenstratSnpEntry -> (Chrom, Int) genomicPosition (EigenstratSnpEntry Chrom c Int p Double _ ByteString _ Char _ Char _) = (Chrom c, Int p) instance Genomic FreqSumEntry where genomicPosition :: FreqSumEntry -> (Chrom, Int) genomicPosition (FreqSumEntry Chrom c Int p Maybe ByteString _ Maybe Double _ Char _ Char _ [Maybe Int] _) = (Chrom c, Int p) instance Genomic PileupRow where genomicPosition :: PileupRow -> (Chrom, Int) genomicPosition (PileupRow Chrom c Int p Char _ [String] _ [[Strand]] _) = (Chrom c, Int p) instance Genomic VCFentry where genomicPosition :: VCFentry -> (Chrom, Int) genomicPosition (VCFentry Chrom c Int p Maybe ByteString _ ByteString _ [ByteString] _ Maybe Double _ Maybe ByteString _ [ByteString] _ [ByteString] _ [[ByteString]] _) = (Chrom c, Int p) chromFilter :: (Genomic e) => [Chrom] -> e -> Bool chromFilter :: forall e. Genomic e => [Chrom] -> e -> Bool chromFilter [Chrom] exclusionList = (Chrom -> [Chrom] -> Bool forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool `notElem` [Chrom] exclusionList) (Chrom -> Bool) -> (e -> Chrom) -> e -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . e -> Chrom forall a. Genomic a => a -> Chrom genomicChrom genomicFilterThroughBed :: (Monad m, Genomic e) => Producer BedEntry m () -> Producer e m () -> Producer e m () genomicFilterThroughBed :: forall (m :: * -> *) e. (Monad m, Genomic e) => Producer BedEntry m () -> Producer e m () -> Producer e m () genomicFilterThroughBed Producer BedEntry m () bedProd = Producer BedEntry m () -> (e -> (Chrom, Int)) -> Producer e m () -> Producer e m () forall (m :: * -> *) a. Monad m => Producer BedEntry m () -> (a -> (Chrom, Int)) -> Producer a m () -> Producer a m () filterThroughBed Producer BedEntry m () bedProd e -> (Chrom, Int) forall a. Genomic a => a -> (Chrom, Int) genomicPosition