You can see an example in biofasta:

https://github.com/BioHaskell/biofasta/blob/master/src/Bio/Sequence/Fasta.hs

on line 31:

import Bio.Core.Sequence

then lines 37-44:

data Sequence = Seq SeqLabel SeqData (Maybe QualData)
                deriving (Show, Eq)

instance BioSeq Sequence where
  seqid     (Seq lab seq mqual) = SeqLabel {unSL = B.takeWhile (/= '
') $ unSL lab}
  seqheader (Seq lab seq mqual) = lab
  seqdata   (Seq lab seq mqual) = seq
  seqlength (Seq lab seq mqual) = Offset {unOff = B.length $ unSD seq}

The BioSeq typeclass that is used above comes from Bio.Core.Sequence:

http://malde.org/~ketil/biohaskell/biocore/src/Bio/Core/Sequence.hs


-- | The 'BioSeq' class models sequence data, and any data object that
--   represents a biological sequence should implement it.
class BioSeq s where
  seqid     :: s -> SeqLabel -- ^ Sequence identifier (typically first
word of the header)
  seqid = seqlabel
  seqheader :: s -> SeqLabel -- ^ Sequence header (may contain
whitespace), by convention the
                             --   first word matches the 'seqid'
  seqheader = seqlabel
  seqdata   :: s -> SeqData  -- ^ Sequence data
  seqlength :: s -> Offset   -- ^ Sequence length



On Sat, Mar 29, 2014 at 3:07 AM, Vasili I. Galchin <vigalc...@gmail.com>wrote:

> Ketil,
>
>      Maybe you misunderstood my question. Where is the new biocore used??
> Example please.
>
> Vasili
>
>
> On Sat, Mar 29, 2014 at 4:31 AM, Ketil Malde <ke...@malde.org> wrote:
>
>>
>> Vasili I. Galchin <vigalc...@gmail.com> writes:
>>
>> >      I was under the impression that biocore replaces former
>> functionality
>> > like Bio.Sequence; however, just by random reading in
>> > http://hackage.haskell.org/package/bio-0.5.3/src/ .. I don't an import
>> of
>> > Bio.Core. Why?? I am trying to get TwoBit.hs in compliance with module
>> > Bio.Core.
>>
>> The idea is that biocore contains common definitions, but little
>> specific implementation. Which comes as separate libraries, so biofasta,
>> biofastq, etc are implementations for those formats.
>>
>> This way, TwoBit could have its own internal representation (possibly a
>> two-bit array), accessible through the "core" typeclasses.
>>
>> I started to work on making biolib (which is a monolithic library
>> containing all kinds of functionality) depend on biocore, but stumbled
>> upon some difficulties, and forgot about it.
>>
>> -k
>> --
>> If I haven't seen further, it is by standing in the footprints of giants
>>
>
>

Reply via email to