module Bio.Location.Position ( Pos(..), slide, seqNt, seqNtPadded, display )
where
import Control.Monad.Error
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.Ix (Ix)
import Data.List
import Bio.Location.Strand
import Bio.Sequence.SeqData
data Pos = Pos { offset :: !Offset
, strand :: !Strand
}
deriving (Eq, Ord, Show, Read, Ix)
instance Stranded Pos where
revCompl (Pos off str) = Pos off $ revCompl str
slide :: Pos -> Offset -> Pos
slide (Pos off str) doff = Pos (off + doff) str
seqNt :: (Error e, MonadError e m) => SeqData -> Pos -> m Char
seqNt sequ (Pos off str) | off >= 0 && off < LBS.length sequ = return $ stranded str $ sequ `LBS.index` off
| otherwise = throwError $ strMsg $ "position " ++ show off ++ " out of SeqData bounds"
seqNtPadded :: SeqData -> Pos -> Char
seqNtPadded sequ (Pos off str) | off >= 0 && off < LBS.length sequ = stranded str $ sequ `LBS.index` off
| otherwise = 'N'
display :: Pos -> String
display (Pos off str) = show off ++ displayStrand
where displayStrand = case str of
Fwd -> "(+)"
RevCompl -> "(-)"