Skip to content
Snippets Groups Projects
Commit 0d283ccf authored by Sebastian Graf's avatar Sebastian Graf Committed by Andreas Klebinger
Browse files

reverse-complement: Provide own inlinePerformIO

parent d6c01568
No related branches found
No related tags found
1 merge request!39reverse-complement: Provide own inlinePerformIO
Pipeline #34720 failed
......@@ -11,6 +11,8 @@ import Control.Monad
import Foreign
import Data.ByteString.Internal
import System.IO
import GHC.Exts
import GHC.IO (IO(..))
data Buf = Buf !Int !Int !(Ptr Word8)
......@@ -57,6 +59,11 @@ main = allocaArray 82 $ \ line ->
comps = Prelude.zipWith (\ a b -> (fromEnum a, c2w b)) "AaCcGgTtUuMmRrYyKkVvHhDdBb"
"TTGGCCAAAAKKYYRRMMBBDDHHVV"
-- Just like unsafeDupablePerformIO, but we inline it.
{-# INLINE inlinePerformIO #-}
inlinePerformIO :: IO a -> a
inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r
ca :: Ptr Word8
ca = inlinePerformIO $ do
!a <- mallocArray 200
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment