module Biobase.Secondary.Basepair where
import Data.Aeson
import Data.Binary
import Data.Char (toLower, toUpper)
import Data.Ix (Ix(..))
import Data.List as L
import Data.Primitive.Types
import Data.Serialize (Serialize)
import Data.Tuple (swap)
import Data.Vector.Fusion.Stream.Monadic (map,Step(..),flatten)
import Data.Vector.Unboxed.Deriving
import GHC.Base (remInt,quotInt)
import GHC.Generics
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Unboxed as VU
import Text.Read
import Biobase.Types.BioSequence
import Data.PrimitiveArray hiding (Complement(..),map)
import Biobase.Primary
import Biobase.Primary.Nuc.RNA
import Biobase.Primary.Nuc
newtype Basepair = BP { getBP :: Int }
deriving (Eq,Ord,Ix,Generic)
derivingUnbox "Basepair"
[t| Basepair -> Int |] [| getBP |] [| BP |]
instance Binary Basepair
instance Serialize Basepair
instance FromJSON Basepair
instance ToJSON Basepair
instance Index Basepair where
newtype LimitType Basepair = LtBP Basepair
instance IndexStream z => IndexStream (z:.Basepair) where
streamUp (ls:..LtBP (BP l)) (hs:..LtBP (BP h)) = flatten mk step $ streamUp ls hs
where mk z = return (z,l)
step (z,k)
| k > h = return $ Done
| otherwise = return $ Yield (z:.BP k) (z,k+1)
{-# Inline [0] mk #-}
{-# Inline [0] step #-}
{-# Inline streamUp #-}
streamDown (ls:..LtBP (BP l)) (hs:..LtBP (BP h)) = flatten mk step $ streamDown ls hs
where mk z = return (z,h)
step (z,k)
| k < l = return $ Done
| otherwise = return $ Yield (z:.BP k) (z,k-1)
{-# Inline [0] mk #-}
{-# Inline [0] step #-}
{-# Inline streamDown #-}
instance IndexStream Basepair
pattern AA = BP 0
pattern AC = BP 1
pattern AG = BP 2
pattern AU = BP 3
pattern CA = BP 4
pattern CC = BP 5
pattern CG = BP 6
pattern CU = BP 7
pattern GA = BP 8
pattern GC = BP 9
pattern GG = BP 10
pattern GU = BP 11
pattern UA = BP 12
pattern UC = BP 13
pattern UG = BP 14
pattern UU = BP 15
pattern NS = BP 16
pattern NoBP = BP 17
newtype Edge = Edge {unEdge :: Int}
deriving (Eq,Ord,Ix,Generic)
pattern W = Edge 0
pattern S = Edge 1
pattern H = Edge 2
instance Binary Edge
instance Serialize Edge
instance FromJSON Edge
instance ToJSON Edge
instance Show Edge where
show H = "H"
show S = "S"
show W = "W"
instance Read Edge where
readPrec = parens $ do
Ident s <- lexP
return $ case s of
"H" -> H
"S" -> S
"W" -> W
_ -> error $ "read Edge: " ++ s
instance Bounded Edge where
minBound = W
maxBound = H
instance Enum Edge where
toEnum = Edge
fromEnum = unEdge
derivingUnbox "Edge"
[t| Edge -> Int |] [| unEdge |] [| Edge |]
newtype CTisomerism = CT {unCT :: Int}
deriving (Eq,Ord,Ix,Generic)
pattern Cis = CT 0
pattern Trn = CT 1
instance Binary CTisomerism
instance Serialize CTisomerism
instance FromJSON CTisomerism
instance ToJSON CTisomerism
instance Show CTisomerism where
show Cis = "C"
show Trn = "T"
instance Read CTisomerism where
readPrec = parens $ do
Ident s <- lexP
return $ case s of
"C" -> Cis
"T" -> Trn
_ -> error $ "read CTisomerism: " ++ s
instance Bounded CTisomerism where
minBound = Cis
maxBound = Trn
instance Enum CTisomerism where
toEnum = CT
fromEnum = unCT
derivingUnbox "CTisomerism"
[t| CTisomerism -> Int |] [| unCT |] [| CT |]
type PairIdx = (Int,Int)
type Pair n = (Letter RNA n, Letter RNA n)
type ExtPairAnnotation = (CTisomerism,Edge,Edge)
type ExtPairIdx = (PairIdx,ExtPairAnnotation)
type ExtPair n = (Pair n, ExtPairAnnotation)
pattern CHH = (Cis,H,H)
pattern CHS = (Cis,H,S)
pattern CHW = (Cis,H,W)
pattern CSH = (Cis,S,H)
pattern CSS = (Cis,S,S)
pattern CSW = (Cis,S,W)
pattern CWH = (Cis,W,H)
pattern CWS = (Cis,W,S)
pattern CWW = (Cis,W,W)
pattern THH = (Trn,H,H)
pattern THS = (Trn,H,S)
pattern THW = (Trn,H,W)
pattern TSH = (Trn,S,H)
pattern TSS = (Trn,S,S)
pattern TSW = (Trn,S,W)
pattern TWH = (Trn,W,H)
pattern TWS = (Trn,W,S)
pattern TWW = (Trn,W,W)