module BioInf.ViennaRNA.Bindings.FFI.Duplex
( Duplex (..)
, ffiDuplexFold
) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Control.Applicative
import Control.Monad
import Foreign.C.String
import Foreign.C.Types
import Foreign.Marshal.Alloc
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable
import GHC.Float
import qualified Data.Array.IArray as A
import Unsafe.Coerce
import BioInf.ViennaRNA.Bindings.FFI.Utils
type DuplexPtr = C2HSImp.Ptr (Duplex)
data Duplex = Duplex
{ i :: !Int
, j :: !Int
, end :: !Int
, structure :: !String
, energy :: !Double
, energyBacktrack :: !Double
, openingBacktrackX :: !Double
, openingBacktrackY :: !Double
, offset :: !Int
, dG1 :: !Double
, dG2 :: !Double
, ddG :: !Double
, tb :: !Int
, te :: !Int
, qb :: !Int
, qe :: !Int
}
deriving (Show)
instance Storable Duplex where
sizeOf _ = 104
alignment _ = sizeOf (undefined :: CDouble)
peek p = Duplex
<$> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p)
<*> (peekCAString =<< ((\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p))
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO C2HSImp.CDouble}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 32 :: IO C2HSImp.CDouble}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 40 :: IO C2HSImp.CDouble}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 48 :: IO C2HSImp.CDouble}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 56 :: IO C2HSImp.CInt}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 64 :: IO C2HSImp.CDouble}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 72 :: IO C2HSImp.CDouble}) p)
<*> liftM realToFrac ((\ptr -> do {C2HSImp.peekByteOff ptr 80 :: IO C2HSImp.CDouble}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 88 :: IO C2HSImp.CInt}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 92 :: IO C2HSImp.CInt}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 96 :: IO C2HSImp.CInt}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 100 :: IO C2HSImp.CInt}) p)
ffiDuplexFold :: String -> String -> IO Duplex
ffiDuplexFold l r =
withCAString l $ \cl ->
withCAString r $ \cr ->
alloca $ \ptr -> do
d <- duplexfold_p ptr cl cr >> peek ptr
return d
foreign import ccall "ffiwrap_duplexfold" duplexfold_p :: DuplexPtr -> CString -> CString -> IO ()