-- GENERATED by C->Haskell Compiler, version 0.28.1 Switcheroo, 1 April 2016 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "./BioInf/ViennaRNA/Bindings/FFI/Duplex.chs" #-}

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           Data.ByteString.Char8
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)
{-# LINE 27 "./BioInf/ViennaRNA/Bindings/FFI/Duplex.chs" #-}


data Duplex = Duplex
  { i                 :: {-# UNPACK #-} !Int
  , j                 :: {-# UNPACK #-} !Int
  , end               :: {-# UNPACK #-} !Int
  , structure         ::                !ByteString
  , energy            :: {-# UNPACK #-} !Double
  , energyBacktrack   :: {-# UNPACK #-} !Double
  , openingBacktrackX :: {-# UNPACK #-} !Double
  , openingBacktrackY :: {-# UNPACK #-} !Double
  , offset            :: {-# UNPACK #-} !Int
  , dG1               :: {-# UNPACK #-} !Double
  , dG2               :: {-# UNPACK #-} !Double
  , ddG               :: {-# UNPACK #-} !Double
  , tb                :: {-# UNPACK #-} !Int
  , te                :: {-# UNPACK #-} !Int
  , qb                :: {-# UNPACK #-} !Int
  , qe                :: {-# UNPACK #-} !Int
  }
  deriving (Show)

instance Storable Duplex where
  sizeOf _ = 104
{-# LINE 50 "./BioInf/ViennaRNA/Bindings/FFI/Duplex.chs" #-}

  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)
    <*> (packCString =<<   ((\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 :: ByteString -> ByteString -> IO Duplex
ffiDuplexFold l r =
  useAsCString l $ \cl  ->
  useAsCString 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 ()