module Biobase.Primary.Nuc.RNA where

import           Control.Category ((>>>))
import           Control.Lens (Iso', iso)
import           Data.Aeson
import           Data.Char (toUpper)
import           Data.Data
import           Data.Ix (Ix(..))
import           Data.Primitive.Types
import           Data.String
import           Data.Tuple (swap)
import           Data.Typeable
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Unboxed as VU

import           Biobase.Types.BioSequence (RNA)

import           Biobase.Primary.Bounds
import           Biobase.Primary.Letter



pattern $bA :: Letter RNA n
$mA :: forall r k (n :: k).
Letter RNA n -> (Void# -> r) -> (Void# -> r) -> r
A = Letter 0  Letter RNA n
pattern $bC :: Letter RNA n
$mC :: forall r k (n :: k).
Letter RNA n -> (Void# -> r) -> (Void# -> r) -> r
C = Letter 1  Letter RNA n
pattern $bG :: Letter RNA n
$mG :: forall r k (n :: k).
Letter RNA n -> (Void# -> r) -> (Void# -> r) -> r
G = Letter 2  Letter RNA n
pattern $bU :: Letter RNA n
$mU :: forall r k (n :: k).
Letter RNA n -> (Void# -> r) -> (Void# -> r) -> r
U = Letter 3  Letter RNA n
pattern $bN :: Letter RNA n
$mN :: forall r k (n :: k).
Letter RNA n -> (Void# -> r) -> (Void# -> r) -> r
N = Letter 4  Letter RNA n

instance Bounded (Letter RNA n) where
    minBound :: Letter RNA n
minBound = Letter RNA n
forall k (n :: k). Letter RNA n
A
    maxBound :: Letter RNA n
maxBound = Letter RNA n
forall k (n :: k). Letter RNA n
N

instance Enum (Letter RNA n) where
    succ :: Letter RNA n -> Letter RNA n
succ Letter RNA n
N          = [Char] -> Letter RNA n
forall a. HasCallStack => [Char] -> a
error [Char]
"succ/N:RNA"
    succ (Letter Int
x) = Int -> Letter RNA n
forall k seqTy (nameTy :: k). Int -> Letter seqTy nameTy
Letter (Int -> Letter RNA n) -> Int -> Letter RNA n
forall a b. (a -> b) -> a -> b
$ Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1
    pred :: Letter RNA n -> Letter RNA n
pred Letter RNA n
A          = [Char] -> Letter RNA n
forall a. HasCallStack => [Char] -> a
error [Char]
"pred/A:RNA"
    pred (Letter Int
x) = Int -> Letter RNA n
forall k seqTy (nameTy :: k). Int -> Letter seqTy nameTy
Letter (Int -> Letter RNA n) -> Int -> Letter RNA n
forall a b. (a -> b) -> a -> b
$ Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1
    toEnum :: Int -> Letter RNA n
toEnum Int
k | Int
kInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
0 Bool -> Bool -> Bool
&& Int
kInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=Int
4 = Int -> Letter RNA n
forall k seqTy (nameTy :: k). Int -> Letter seqTy nameTy
Letter Int
k
    toEnum Int
k                = [Char] -> Letter RNA n
forall a. HasCallStack => [Char] -> a
error ([Char] -> Letter RNA n) -> [Char] -> Letter RNA n
forall a b. (a -> b) -> a -> b
$ [Char]
"toEnum/Letter RNA " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
k
    fromEnum :: Letter RNA n -> Int
fromEnum (Letter Int
k) = Int
k

instance LetterChar RNA n where
  letterChar :: Letter RNA n -> Char
letterChar = Letter RNA n -> Char
forall k (n :: k). Letter RNA n -> Char
rnaChar
  charLetter :: Char -> Letter RNA n
charLetter = Char -> Letter RNA n
forall k (n :: k). Char -> Letter RNA n
charRNA

instance ToJSON (Letter RNA n) where
  toJSON :: Letter RNA n -> Value
toJSON = Char -> Value
forall a. ToJSON a => a -> Value
toJSON (Char -> Value) -> (Letter RNA n -> Char) -> Letter RNA n -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Letter RNA n -> Char
forall k t (n :: k). LetterChar t n => Letter t n -> Char
letterChar

instance FromJSON (Letter RNA n) where
  parseJSON :: Value -> Parser (Letter RNA n)
parseJSON = (Char -> Letter RNA n) -> Parser Char -> Parser (Letter RNA n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Letter RNA n
forall k t (n :: k). LetterChar t n => Char -> Letter t n
charLetter (Parser Char -> Parser (Letter RNA n))
-> (Value -> Parser Char) -> Value -> Parser (Letter RNA n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Char
forall a. FromJSON a => Value -> Parser a
parseJSON

-- We encode 'Primary RNA' directly as a string.
--
-- TODO we can't anymore, because this is not a newtype, just a type.

--instance ToJSON (Primary RNA) where
--  toJSON = toJSON . VU.toList . VU.map letterChar
--
--instance FromJSON (Primary RNA) where
--  parseJSON = fmap (primary ∷ String → Primary RNA) . parseJSON


acgu  [Letter RNA n]
acgu :: [Letter RNA n]
acgu = [Letter RNA n
forall k (n :: k). Letter RNA n
A .. Letter RNA n
forall k (n :: k). Letter RNA n
U]

charRNA :: Char -> Letter RNA n
charRNA = Char -> Char
toUpper (Char -> Char) -> (Char -> Letter RNA n) -> Char -> Letter RNA n
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> \case
    Char
'A' -> Letter RNA n
forall k (n :: k). Letter RNA n
A
    Char
'C' -> Letter RNA n
forall k (n :: k). Letter RNA n
C
    Char
'G' -> Letter RNA n
forall k (n :: k). Letter RNA n
G
    Char
'U' -> Letter RNA n
forall k (n :: k). Letter RNA n
U
    Char
_   -> Letter RNA n
forall k (n :: k). Letter RNA n
N
{-# INLINE charRNA #-}

rnaChar :: Letter RNA n -> Char
rnaChar = \case
  Letter RNA n
A -> Char
'A'
  Letter RNA n
C -> Char
'C'
  Letter RNA n
G -> Char
'G'
  Letter RNA n
U -> Char
'U'
  Letter RNA n
N -> Char
'N'
  Letter RNA n
_ -> Char
'\9888'
{-# INLINE rnaChar #-}            

-- | An isomorphism from 'Char' to 'Letter RNA'. This assumes that the
-- underlying @Char@s actually represent an RNA sequence. This allows typesafe
-- modification of RNA sequences since only @[A,C,G,U,N]@ are allowed.

crna  Iso' Char (Letter RNA n)
crna :: p (Letter RNA n) (f (Letter RNA n)) -> p Char (f Char)
crna = (Char -> Letter RNA n)
-> (Letter RNA n -> Char)
-> Iso Char Char (Letter RNA n) (Letter RNA n)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Char -> Letter RNA n
forall k (n :: k). Char -> Letter RNA n
charRNA Letter RNA n -> Char
forall k (n :: k). Letter RNA n -> Char
rnaChar

instance Show (Letter RNA n) where
    show :: Letter RNA n -> [Char]
show Letter RNA n
c = [Letter RNA n -> Char
forall k (n :: k). Letter RNA n -> Char
rnaChar Letter RNA n
c]

instance Read (Letter RNA n) where
  readsPrec :: Int -> ReadS (Letter RNA n)
readsPrec Int
p [] = []
  readsPrec Int
p (Char
x:[Char]
xs)
    | Char
xChar -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
' ' = Int -> ReadS (Letter RNA n)
forall a. Read a => Int -> ReadS a
readsPrec Int
p [Char]
xs
    | Bool
otherwise = [(Char -> Letter RNA n
forall k (n :: k). Char -> Letter RNA n
charRNA Char
x, [Char]
xs)]

rnaSeq  MkPrimary p RNA n  p  Primary RNA n
rnaSeq :: p -> Primary RNA n
rnaSeq = p -> Primary RNA n
forall k c t (n :: k). MkPrimary c t n => c -> Primary t n
primary

instance MkPrimary (VU.Vector Char) RNA n where
    primary :: Vector Char -> Primary RNA n
primary = (Char -> Letter RNA n) -> Vector Char -> Primary RNA n
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
VU.map Char -> Letter RNA n
forall k (n :: k). Char -> Letter RNA n
charRNA

instance IsString [Letter RNA n] where
    fromString :: [Char] -> [Letter RNA n]
fromString = (Char -> Letter RNA n) -> [Char] -> [Letter RNA n]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Letter RNA n
forall k (n :: k). Char -> Letter RNA n
charRNA

viennaPairs :: [(Letter RNA n, Letter RNA n)]
viennaPairs = [ (Letter RNA n
forall k (n :: k). Letter RNA n
C,Letter RNA n
forall k (n :: k). Letter RNA n
G), (Letter RNA n
forall k (n :: k). Letter RNA n
G,Letter RNA n
forall k (n :: k). Letter RNA n
C), (Letter RNA n
forall k (n :: k). Letter RNA n
G,Letter RNA n
forall k (n :: k). Letter RNA n
U), (Letter RNA n
forall k (n :: k). Letter RNA n
U,Letter RNA n
forall k (n :: k). Letter RNA n
G), (Letter RNA n
forall k (n :: k). Letter RNA n
A,Letter RNA n
forall k (n :: k). Letter RNA n
U), (Letter RNA n
forall k (n :: k). Letter RNA n
U,Letter RNA n
forall k (n :: k). Letter RNA n
A) ]
viennaPairsNN :: [(Letter RNA n, Letter RNA n)]
viennaPairsNN = [(Letter RNA n, Letter RNA n)]
forall k k (n :: k) (n :: k). [(Letter RNA n, Letter RNA n)]
viennaPairs [(Letter RNA n, Letter RNA n)]
-> [(Letter RNA n, Letter RNA n)] -> [(Letter RNA n, Letter RNA n)]
forall a. [a] -> [a] -> [a]
++ [ (Letter RNA n
forall k (n :: k). Letter RNA n
N,Letter RNA n
forall k (n :: k). Letter RNA n
N) ]