{-| Data type for a sequence position. Zero-based 'Offset' / 'Int64' indices are used throughout, to facilitate direct use of indexing functions on 'SeqData'. -} module Bio.Location.Position ( -- * Sequence positions Pos(..) -- * Manipulating positions , slide -- * Extracting sequences , seqNt, seqNtPadded -- * Displaying positions , 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 -- | Position in a sequence data Pos = Pos { offset :: !Offset -- ^ 0-based index of the position , strand :: !Strand -- ^ Strand of the position } deriving (Eq, Ord, Show, Read, Ix) instance Stranded Pos where revCompl (Pos off str) = Pos off $ revCompl str -- | Returns a position resulting from sliding the original position -- along the sequence by a specified offset. A positive offset will -- move the position away from the 5\' end of the forward stand of the -- sequence regardless of the strand of the position itself. Thus, -- -- > slide (revCompl pos) off == revCompl (slide pos off) slide :: Pos -> Offset -> Pos slide (Pos off str) doff = Pos (off + doff) str -- | Extract the nucleotide at a specific sequence position. If the -- position lies outside the bounds of the sequence, an error results. 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" -- | As 'seqNt', extract the nucleotide at a specific sequence -- position, but return @N@ when the position lies outside the -- bounds of the sequence. -- -- > seqNtPadded sequ pos == (either 'N' id . seqNt sequ) pos seqNtPadded :: SeqData -> Pos -> Char seqNtPadded sequ (Pos off str) | off >= 0 && off < LBS.length sequ = stranded str $ sequ `LBS.index` off | otherwise = 'N' -- | Display a human-friendly, zero-based representation of a sequence position. display :: Pos -> String display (Pos off str) = show off ++ displayStrand where displayStrand = case str of Fwd -> "(+)" RevCompl -> "(-)"