On 13 July 2012 13:17, Dan Fornika <dforn...@gmail.com> wrote:

> I'm having a bit of trouble here, I think I'm missing something that
> should be pretty simple.  I'm trying to compile a file that uses the (!)
> function to access a single base of a sequence based on an Offset (an index
> into the sequence).
>
> The function, taken from Bio.Sequence.SeqData, is:
>
> {-# INLINE (!) #-}
> (!) :: Sequence -> Offset -> Char
> (!) (Seq _ bs _) = B.index bs
>
> But when I try to compile, I get the following error:
>
> Couldn't match expected type `Offset'
>             with actual type `GHC.Int.Int64'
> Expected type: Offset -> Char
>   Actual type: GHC.Int.Int64 -> Char
> In the return type of a call of `B.index'
> In the expression: B.index bs
>
> Which is confusing, because the definition of Offset is:
>
> newtype Offset = Offset { unOff :: Int64 } deriving
> (Show,Eq,Ord,Num,Enum,Real,**Integral,Typeable)
>
> So I can see how to go from Offset -> Int64 with unOff, and I see how I
> can make some Int64 into an Offset the type constructor Offset, but how do
> I satisfy that type mismatch error?
>
>
Hi Dan,

I think the version of Bio.Sequence.SeqData that you took that function
from is using "type Offset = Int64" which is why it works there.  If you
are using that newtype that you listed then you need to compose with the
unOff function:

(!) :: Sequence -> Offset -> Char
(!) (Seq _ bs _) = B.index bs . unOff

I've not tested that, but hopefully it helps.

Cheers,

-- David Powell
_______________________________________________
Biohaskell mailing list
Biohaskell@biohaskell.org
http://malde.org/cgi-bin/mailman/listinfo/biohaskell

Reply via email to