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
newtype ReadingFrame = ReadingFrame { getReadingFrame ∷ Int }
deriving (Eq,Ord,Generic,Show)
makeWrapped ''ReadingFrame
rf ∷ Prism' Int ReadingFrame
{-# Inline rf #-}
rf = prism' getReadingFrame $ \k → let ak = abs k in
if (ak <= 3 && ak >= 1) then Just (ReadingFrame k) else Nothing
strandRF ∷ Lens' ReadingFrame Strand
{-# Inline strandRF #-}
strandRF = lens (\(ReadingFrame k) → if k < 0 then MinusStrand else PlusStrand)
(\(ReadingFrame k) s → ReadingFrame $ if s == PlusStrand then abs k else (negate $ abs k))
instance Enum ReadingFrame where
{-# Inline toEnum #-}
toEnum k = case k^?rf of Just rf → rf ; Nothing → error $ show k ++ " is not a legal reading frame"
{-# Inline fromEnum #-}
fromEnum = getReadingFrame
fromIndex ∷ Index 1 → ReadingFrame
{-# Inline fromIndex #-}
fromIndex i = ReadingFrame $ (toInt0 i `mod` 3) + 1