Skip to content

Commit

Permalink
Require c2hs version 0.16.3 and remove C2HS library
Browse files Browse the repository at this point in the history
Require c2hs 0.6.13 (for the new `alignof' macro) and get rid of the dependency on the C2HS library module by using standard Prelude functions.
  • Loading branch information
Stefan Kersten committed May 9, 2011
1 parent 7ca7b36 commit ec7a178
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 228 deletions.
220 changes: 0 additions & 220 deletions C2HS.hs

This file was deleted.

22 changes: 16 additions & 6 deletions Sound/File/Sndfile/Interface.chs
@@ -1,16 +1,26 @@
{-# LANGUAGE ForeignFunctionInterface #-}
module Sound.File.Sndfile.Interface where

import C2HS
import Control.Monad (liftM, when)
import Data.Bits ((.|.), (.&.))
import Control.Monad (liftM, when)
import Foreign
import Foreign.C
import qualified Sound.File.Sndfile.Exception as E
import System.IO.Unsafe (unsafePerformIO)

#include <sndfile.h>

{#context lib="libsndfile" prefix="sf"#}

-- ====================================================================
-- Utilities

-- | Convert a C enumeration to Haskell.
cToEnum :: (Integral i, Enum e) => i -> e
cToEnum = toEnum . fromIntegral

-- | Convert a Haskell enumeration to C.
cFromEnum :: (Enum e, Integral i) => e -> i
cFromEnum = fromIntegral . fromEnum

-- ====================================================================
-- Basic types

Expand Down Expand Up @@ -174,7 +184,7 @@ defaultInfo = Info 0 0 0 defaultFormat 0 False
{-# NOINLINE checkFormat #-}
checkFormat :: Info -> Bool
checkFormat info =
unsafePerformIO (with info (liftM cToBool . {#call unsafe sf_format_check#} . castPtr))
unsafePerformIO (with info (liftM toBool . {#call unsafe sf_format_check#} . castPtr))

-- Storable instance for Info
instance Storable (Info) where
Expand Down Expand Up @@ -295,7 +305,7 @@ hSeek' ioMode (Handle _ handle) seekMode frames = do
n <- liftM fromIntegral $
{#call unsafe sf_seek#}
handle
(cIntConv frames)
(fromIntegral frames)
((cFromEnum seekMode) .|. (case ioMode of
Nothing -> 0
Just m -> cFromEnum m))
Expand Down
3 changes: 1 addition & 2 deletions hsndfile.cabal
Expand Up @@ -28,8 +28,7 @@ Library
Build-Tools: c2hs >= 0.16.3
Exposed-Modules: Sound.File.Sndfile
Sound.File.Sndfile.Buffer
Other-Modules: C2HS
Sound.File.Sndfile.Buffer.Internal
Other-Modules: Sound.File.Sndfile.Buffer.Internal
Sound.File.Sndfile.Buffer.Sample
Sound.File.Sndfile.Exception
Sound.File.Sndfile.Interface
Expand Down

0 comments on commit ec7a178

Please sign in to comment.