Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Location l where
- strand :: l -> Strand
- length :: l -> Offset
- bounds :: l -> (Offset, Offset)
- startPos :: l -> Pos
- endPos :: l -> Pos
- allPos :: l -> [Pos]
- seqData :: (SeqLike s, Stranded s) => s -> l -> Maybe s
- seqDataPad :: (SeqLike s, Stranded s) => s -> l -> s
- posInto :: Pos -> l -> Maybe Pos
- posOutof :: Pos -> l -> Maybe Pos
- clocInto :: ContigLoc -> l -> Maybe ContigLoc
- clocOutof :: ContigLoc -> l -> Maybe l
- extend :: (Offset, Offset) -> l -> l
- offsetWithin :: Offset -> l -> Bool
- posWithin :: Pos -> l -> Bool
- contigOverlaps :: ContigLoc -> l -> Bool
- toContigs :: l -> [ContigLoc]
- overlaps :: (Location l1, Location l2) => l1 -> l2 -> Bool
- data ContigLoc
- offset5 :: ContigLoc -> Offset
- fromStartEnd :: Offset -> Offset -> ContigLoc
- fromPosLen :: Pos -> Offset -> ContigLoc
- fromBoundsStrand :: Offset -> Offset -> Strand -> ContigLoc
- slide :: Offset -> ContigLoc -> ContigLoc
Sequence locations
bounds :: l -> (Offset, Offset) Source
The bounds of a sequence location. This is a pair consisting of the lowest and highest sequence offsets covered by the region. The bounds ignore the strand of the sequence location, and the first element of the pair will always be lower than the second.
Sequence position of the start of the location. This is the 5'
end on the location strand, which will have a higher offset than
endPos
if the location is on the Minus
strand.
Sequence position of the end of the location, as described in
startPos
.
List of sequence positions in the location, in order from the 5' end to the 3' end of the location strand.
seqData :: (SeqLike s, Stranded s) => s -> l -> Maybe s Source
Extract Just
the nucleotide SeqLike
for the sequence
location, or Nothing
if f any part of the location lies outside
the bounds of the sequence.
seqDataPad :: (SeqLike s, Stranded s) => s -> l -> s Source
As seqData
, extract the nucleotide subsequence for the
location, but any positions in the location lying outside the
bounds of the sequence are returned as N
.
posInto :: Pos -> l -> Maybe Pos Source
Given a sequence position and a sequence location relative to
the same sequence, compute a new position representing the
original position relative to the subsequence defined by the
location. If the sequence position lies outside of the sequence
location, Nothing
is returned; thus, the offset of the new
position will always be in the range [0, length l - 1]
.
posOutof :: Pos -> l -> Maybe Pos Source
Given a sequence location and a sequence position within that
location, compute a new position representing the original
position relative to the outer sequence. If the sequence
position lies outside the location, Nothing
is returned.
This function inverts posInto
when the sequence position lies
within the position is actually within the location.
clocInto :: ContigLoc -> l -> Maybe ContigLoc Source
For an enclosing location and a sublocation in the same
coordinate system, find the image of the sublocation relative to
the enclosing location. For example, if the enclosing location
spans (100, 150) and the sublocation is (110, 120) then
clocInto
will be (10, 20).
clocOutof :: ContigLoc -> l -> Maybe l Source
Returns a sequence location produced by finding the inverse
image of a sublocation, with coordinates given relative to an
enclosing location, in the coordinate system of the enclosing
location. For example, if the enclosing location spans (100,
150) and the sublocation is (10, 20) then clocOutof
will be
(110, 120).
extend :: (Offset, Offset) -> l -> l Source
Returns a sequence location produced by extending the original
location on each end, based on a pair of (5' extension, /3'
extension/). The 5' extension is applied to the 5' end of the
location on the location strand; if the location is on the
Minus
strand, the 5' end will have a higher offset than the
3' end and this offset will increase by the amount of the 5'
extension. Similarly, the 3' extension is applied to the 3'
end of the location.
offsetWithin :: Offset -> l -> Bool Source
Returns True
when a sequence offset lies within a sequence
location on the same sequence
posWithin :: Pos -> l -> Bool Source
Returns True
when a sequence position lies within a sequence
location on the same sequence, and occupies the same strand.
contigOverlaps :: ContigLoc -> l -> Bool Source
Returns True
when two sequence locations overlap at any
position.
toContigs :: l -> [ContigLoc] Source
Contigs that comprise the location
Contiguous sequence locations
Contiguous sequence location defined by a span of sequence positions, lying on a specific strand of the sequence.
fromStartEnd :: Offset -> Offset -> ContigLoc Source
Create a sequence location lying between 0-based starting and
ending offsets. When start < end
, the location
be on the forward strand, otherwise it will be on the
reverse complement strand.
fromPosLen :: Pos -> Offset -> ContigLoc Source
Create a sequence location from the sequence position of the start of the location and the length of the position. The strand of the location, and the direction it extends from the starting position, are determined by the strand of the starting position.
fromBoundsStrand :: Offset -> Offset -> Strand -> ContigLoc Source
Create a sequence location between 0-based starting and ending bounds with a specified strand.
Transforming locations
slide :: Offset -> ContigLoc -> ContigLoc Source
Returns a location resulting from sliding the original location along the sequence by a specified offset. A positive offset will move the location away from the 5' end of the forward stand of the sequence regardless of the strand of the location itself. Thus,
slide (revCompl cloc) off == revCompl (slide cloc off)