-- | Stranded reading frames.

module Biobase.Types.ReadingFrame where

import Control.Lens hiding (Index)
import GHC.Generics hiding (from)

import Biobase.Types.Index (Index, toInt0)
import Biobase.Types.Strand



-- | The Reading frame. Sequence indexing starts at position 1, which starts
-- reading frame 1. Reading frame 2 and 3 start at position 2 and 3
-- respectively.

newtype ReadingFrame = ReadingFrame { ReadingFrame -> Int
getReadingFrame  Int }
  deriving (ReadingFrame -> ReadingFrame -> Bool
(ReadingFrame -> ReadingFrame -> Bool)
-> (ReadingFrame -> ReadingFrame -> Bool) -> Eq ReadingFrame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadingFrame -> ReadingFrame -> Bool
$c/= :: ReadingFrame -> ReadingFrame -> Bool
== :: ReadingFrame -> ReadingFrame -> Bool
$c== :: ReadingFrame -> ReadingFrame -> Bool
Eq,Eq ReadingFrame
Eq ReadingFrame
-> (ReadingFrame -> ReadingFrame -> Ordering)
-> (ReadingFrame -> ReadingFrame -> Bool)
-> (ReadingFrame -> ReadingFrame -> Bool)
-> (ReadingFrame -> ReadingFrame -> Bool)
-> (ReadingFrame -> ReadingFrame -> Bool)
-> (ReadingFrame -> ReadingFrame -> ReadingFrame)
-> (ReadingFrame -> ReadingFrame -> ReadingFrame)
-> Ord ReadingFrame
ReadingFrame -> ReadingFrame -> Bool
ReadingFrame -> ReadingFrame -> Ordering
ReadingFrame -> ReadingFrame -> ReadingFrame
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReadingFrame -> ReadingFrame -> ReadingFrame
$cmin :: ReadingFrame -> ReadingFrame -> ReadingFrame
max :: ReadingFrame -> ReadingFrame -> ReadingFrame
$cmax :: ReadingFrame -> ReadingFrame -> ReadingFrame
>= :: ReadingFrame -> ReadingFrame -> Bool
$c>= :: ReadingFrame -> ReadingFrame -> Bool
> :: ReadingFrame -> ReadingFrame -> Bool
$c> :: ReadingFrame -> ReadingFrame -> Bool
<= :: ReadingFrame -> ReadingFrame -> Bool
$c<= :: ReadingFrame -> ReadingFrame -> Bool
< :: ReadingFrame -> ReadingFrame -> Bool
$c< :: ReadingFrame -> ReadingFrame -> Bool
compare :: ReadingFrame -> ReadingFrame -> Ordering
$ccompare :: ReadingFrame -> ReadingFrame -> Ordering
$cp1Ord :: Eq ReadingFrame
Ord,(forall x. ReadingFrame -> Rep ReadingFrame x)
-> (forall x. Rep ReadingFrame x -> ReadingFrame)
-> Generic ReadingFrame
forall x. Rep ReadingFrame x -> ReadingFrame
forall x. ReadingFrame -> Rep ReadingFrame x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadingFrame x -> ReadingFrame
$cfrom :: forall x. ReadingFrame -> Rep ReadingFrame x
Generic,Int -> ReadingFrame -> ShowS
[ReadingFrame] -> ShowS
ReadingFrame -> String
(Int -> ReadingFrame -> ShowS)
-> (ReadingFrame -> String)
-> ([ReadingFrame] -> ShowS)
-> Show ReadingFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadingFrame] -> ShowS
$cshowList :: [ReadingFrame] -> ShowS
show :: ReadingFrame -> String
$cshow :: ReadingFrame -> String
showsPrec :: Int -> ReadingFrame -> ShowS
$cshowsPrec :: Int -> ReadingFrame -> ShowS
Show)
makeWrapped ''ReadingFrame

-- | Convert between @+1 ... +3@ and @ReadingFrame@.

rf  Prism' Int ReadingFrame
{-# Inline rf #-}
rf :: p ReadingFrame (f ReadingFrame) -> p Int (f Int)
rf = (ReadingFrame -> Int)
-> (Int -> Maybe ReadingFrame)
-> Prism Int Int ReadingFrame ReadingFrame
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ReadingFrame -> Int
getReadingFrame ((Int -> Maybe ReadingFrame)
 -> Prism Int Int ReadingFrame ReadingFrame)
-> (Int -> Maybe ReadingFrame)
-> Prism Int Int ReadingFrame ReadingFrame
forall a b. (a -> b) -> a -> b
$ \Int
k  let ak :: Int
ak = Int -> Int
forall a. Num a => a -> a
abs Int
k in
  if (Int
ak Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<=  Int
3 Bool -> Bool -> Bool
&& Int
ak Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1) then ReadingFrame -> Maybe ReadingFrame
forall a. a -> Maybe a
Just (Int -> ReadingFrame
ReadingFrame Int
k) else Maybe ReadingFrame
forall a. Maybe a
Nothing

-- | A lens for the strand

strandRF  Lens' ReadingFrame Strand
{-# Inline strandRF #-}
strandRF :: (Strand -> f Strand) -> ReadingFrame -> f ReadingFrame
strandRF = (ReadingFrame -> Strand)
-> (ReadingFrame -> Strand -> ReadingFrame)
-> Lens ReadingFrame ReadingFrame Strand Strand
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(ReadingFrame Int
k)  if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then Strand
MinusStrand else Strand
PlusStrand)
                (\(ReadingFrame Int
k) Strand
s  Int -> ReadingFrame
ReadingFrame (Int -> ReadingFrame) -> Int -> ReadingFrame
forall a b. (a -> b) -> a -> b
$ if Strand
s Strand -> Strand -> Bool
forall a. Eq a => a -> a -> Bool
== Strand
PlusStrand then Int -> Int
forall a. Num a => a -> a
abs Int
k else (Int -> Int
forall a. Num a => a -> a
negate (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Int
forall a. Num a => a -> a
abs Int
k))

-- |
--
-- @pred@ and @succ@ are correct, if the input is a legal 'ReadingFrame'.

instance Enum ReadingFrame where
  {-# Inline toEnum #-}
  toEnum :: Int -> ReadingFrame
toEnum Int
k = case Int
kInt
-> Getting (First ReadingFrame) Int ReadingFrame
-> Maybe ReadingFrame
forall s a. s -> Getting (First a) s a -> Maybe a
^?Getting (First ReadingFrame) Int ReadingFrame
Prism Int Int ReadingFrame ReadingFrame
rf of Just ReadingFrame
rf  ReadingFrame
rf ; Maybe ReadingFrame
Nothing  String -> ReadingFrame
forall a. HasCallStack => String -> a
error (String -> ReadingFrame) -> String -> ReadingFrame
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is not a legal reading frame"
  {-# Inline fromEnum #-}
  fromEnum :: ReadingFrame -> Int
fromEnum = ReadingFrame -> Int
getReadingFrame

-- |
--
-- TODO should this be a type class, since we might reasonably want to
-- construct from a number of possible indices?

fromIndex  Index 1  ReadingFrame
{-# Inline fromIndex #-}
fromIndex :: Index 1 -> ReadingFrame
fromIndex Index 1
i = Int -> ReadingFrame
ReadingFrame (Int -> ReadingFrame) -> Int -> ReadingFrame
forall a b. (a -> b) -> a -> b
$ (Index 1 -> Int
forall (t :: Nat). KnownNat t => Index t -> Int
toInt0 Index 1
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
3) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1