BiobaseTypes-0.2.1.0: Collection of types for bioinformatics
Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Location

Description

Annotate the genomic Location of features or elements. A Location is always contiguous, using strand, 0-based position, and length. Transformation to different systems of annotation is made possible.

Synopsis

Documentation

class ModifyLocation posTy seqTy where Source #

Operations on locations.

Methods

locAppendLeft :: seqTy -> Location i posTy seqTy -> Location i posTy seqTy Source #

Append to the left.

locAppendRight :: seqTy -> Location i posTy seqTy -> Location i posTy seqTy Source #

Append to the right.

locSplitAt :: Int -> Location i posTy seqTy -> (Location i posTy seqTy, Location i posTy seqTy) Source #

Split a location.

locLength :: Location i posTy seqTy -> Int Source #

Length of location

locTake :: forall k posTy seqTy (i :: k). ModifyLocation posTy seqTy => Int -> Location i posTy seqTy -> Location i posTy seqTy Source #

locTakeEnd :: forall k posTy seqTy (i :: k). ModifyLocation posTy seqTy => Int -> Location i posTy seqTy -> Location i posTy seqTy Source #

locDrop :: forall k posTy seqTy (i :: k). ModifyLocation posTy seqTy => Int -> Location i posTy seqTy -> Location i posTy seqTy Source #

locDropEnd :: forall k posTy seqTy (i :: k). ModifyLocation posTy seqTy => Int -> Location i posTy seqTy -> Location i posTy seqTy Source #

locSplitEndAt :: forall k posTy seqTy (i :: k). ModifyLocation posTy seqTy => Int -> Location i posTy seqTy -> (Location i posTy seqTy, Location i posTy seqTy) Source #

data Location ident posTy seqTy Source #

Constructors

Location 

Fields

Instances

Instances details
(Typeable ident, Typeable k, Data posTy, Data seqTy) => Data (Location ident posTy seqTy) Source # 
Instance details

Defined in Biobase.Types.Location

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Location ident posTy seqTy -> c (Location ident posTy seqTy) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Location ident posTy seqTy) #

toConstr :: Location ident posTy seqTy -> Constr #

dataTypeOf :: Location ident posTy seqTy -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Location ident posTy seqTy)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Location ident posTy seqTy)) #

gmapT :: (forall b. Data b => b -> b) -> Location ident posTy seqTy -> Location ident posTy seqTy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Location ident posTy seqTy -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Location ident posTy seqTy -> r #

gmapQ :: (forall d. Data d => d -> u) -> Location ident posTy seqTy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Location ident posTy seqTy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Location ident posTy seqTy -> m (Location ident posTy seqTy) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Location ident posTy seqTy -> m (Location ident posTy seqTy) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Location ident posTy seqTy -> m (Location ident posTy seqTy) #

(Show posTy, Show seqTy) => Show (Location ident posTy seqTy) Source # 
Instance details

Defined in Biobase.Types.Location

Methods

showsPrec :: Int -> Location ident posTy seqTy -> ShowS #

show :: Location ident posTy seqTy -> String #

showList :: [Location ident posTy seqTy] -> ShowS #

Generic (Location ident posTy seqTy) Source # 
Instance details

Defined in Biobase.Types.Location

Associated Types

type Rep (Location ident posTy seqTy) :: Type -> Type #

Methods

from :: Location ident posTy seqTy -> Rep (Location ident posTy seqTy) x #

to :: Rep (Location ident posTy seqTy) x -> Location ident posTy seqTy #

Info (BioSequence w) => Info (Location i FwdPosition (BioSequence w)) Source # 
Instance details

Defined in Biobase.Types.Location

(NFData p, NFData s) => NFData (Location i p s) Source # 
Instance details

Defined in Biobase.Types.Location

Methods

rnf :: Location i p s -> () #

Reversing (Location i FwdPosition (BioSequence w)) Source # 
Instance details

Defined in Biobase.Types.Location

Complement (BioSequence w) => Complement (Location i FwdPosition (BioSequence w)) Source # 
Instance details

Defined in Biobase.Types.Location

type Rep (Location ident posTy seqTy) Source # 
Instance details

Defined in Biobase.Types.Location

type Rep (Location ident posTy seqTy) = D1 ('MetaData "Location" "Biobase.Types.Location" "BiobaseTypes-0.2.1.0-KNWEaQoA0aY419BnftjfF1" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) (S1 ('MetaSel ('Just "_locIdentifier") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SequenceIdentifier ident)) :*: (S1 ('MetaSel ('Just "_locPosition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 posTy) :*: S1 ('MetaSel ('Just "_locSequence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 seqTy))))

locSequence :: forall k (ident :: k) posTy seqTy seqTy. Lens (Location (ident :: k) posTy seqTy) (Location (ident :: k) posTy seqTy) seqTy seqTy Source #

locPosition :: forall k (ident :: k) posTy seqTy posTy. Lens (Location (ident :: k) posTy seqTy) (Location (ident :: k) posTy seqTy) posTy posTy Source #

locIdentifier :: forall k (ident :: k) posTy seqTy k (ident :: k). Lens (Location (ident :: k) posTy seqTy) (Location (ident :: k) posTy seqTy) (SequenceIdentifier ident) (SequenceIdentifier ident) Source #

retagLocation :: Location i posTy seqTy -> Location j posTy seqTy Source #

subLocation :: Location i FwdPosition (BioSequence w) -> (FwdPosition, Int) -> Location i FwdPosition (BioSequence w) Source #

Will extract a substring for a given biosequence. It is allowed to hand in partially or not at all overlapping locational information. This will yield empty resulting locations.

This will convert the FwdPosition strand, which in turn allows dealing with reverse-complement searches.

0123456789
   3.3

data PIS i p s Source #

Constructors

PIS 

Fields

Instances

Instances details
(Typeable i, Typeable k, Data p, Data s) => Data (PIS i p s) Source # 
Instance details

Defined in Biobase.Types.Location

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PIS i p s -> c (PIS i p s) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PIS i p s) #

toConstr :: PIS i p s -> Constr #

dataTypeOf :: PIS i p s -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PIS i p s)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PIS i p s)) #

gmapT :: (forall b. Data b => b -> b) -> PIS i p s -> PIS i p s #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PIS i p s -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PIS i p s -> r #

gmapQ :: (forall d. Data d => d -> u) -> PIS i p s -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PIS i p s -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PIS i p s -> m (PIS i p s) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PIS i p s -> m (PIS i p s) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PIS i p s -> m (PIS i p s) #

(Show p, Show s) => Show (PIS i p s) Source # 
Instance details

Defined in Biobase.Types.Location

Methods

showsPrec :: Int -> PIS i p s -> ShowS #

show :: PIS i p s -> String #

showList :: [PIS i p s] -> ShowS #

Reversing (Location i FwdPosition (BioSequence w)) => Reversing (PIS i FwdPosition (BioSequence w)) Source # 
Instance details

Defined in Biobase.Types.Location

Complement (BioSequence w) => Complement (PIS i FwdPosition (BioSequence w)) Source # 
Instance details

Defined in Biobase.Types.Location

pisSuffix :: forall k (i :: k) p s. Lens' (PIS (i :: k) p s) (Maybe (Location i p s)) Source #

pisPrefix :: forall k (i :: k) p s. Lens' (PIS (i :: k) p s) (Maybe (Location i p s)) Source #

pisInfix :: forall k (i :: k) p s. Lens' (PIS (i :: k) p s) (Location i p s) Source #

pis :: forall k (i :: k) p s. Location i p s -> PIS i p s Source #

retagPis :: PIS i p s -> PIS j p s Source #

subPisLocation :: PIS i FwdPosition (BioSequence w) -> (FwdPosition, Int) -> PIS i FwdPosition (BioSequence w) Source #

Given a PIS, this will return the substring indicated by the location in the 2nd argument. Allows for easy substring extraction, and retains the system of prefixinfixsuffix.

It is allowed to hand locations that only partially (or not at all) correspond to the PIS, but then the resulting PIS will be empty!

locAsLength :: Location i FwdPosition (BioSequence w) -> Location i FwdPosition Int Source #

Given a Location with a BioSequence, replace the sequence with its length.

blastRange1 :: Location i FwdPosition Int -> (Int, Int, Strand) Source #

Provides a range in a notation as used by blast, for example. This isomorphism can translate back as well. FwdLocation - 8 4 ^. blastRange1 == 9 6 MinusStrand, since these ranges are 1-based and start and end included.

attachPrefixes :: (Monad m, ModifyLocation p s) => Int -> Stream (Of (PIS i p s)) m r -> Stream (Of (PIS i p s)) m r Source #

For each element, attach the prefix as well. The Int indicates the maximal prefix length to attach.

1 2 3 4 -> 01 12 23 34

TODO are we sure this is correct for MinusStrand?

attachSuffixes :: (Monad m, ModifyLocation p s) => Int -> Stream (Of (PIS i p s)) m r -> Stream (Of (PIS i p s)) m r Source #

For each element, attach the suffix as well.

1 2 3 4 -> 12 23 34 40