Skip to content

Commit

Permalink
Merge pull request #49 from SFrijters/fix-warnings-ghc981
Browse files Browse the repository at this point in the history
Fix warnings for GHC 9.8
  • Loading branch information
Haskell-mouse authored Feb 11, 2024
2 parents 55d29f3 + 97f411d commit 52c3ba6
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 1 deletion.
10 changes: 9 additions & 1 deletion Data/Double/Conversion/Internal/ByteStringBuilder.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE TypeFamilies, TypeOperators #-}
{-# LANGUAGE CPP, TypeFamilies, TypeOperators #-}

-- |
-- Module : Data.Double.Conversion.ByteStringBuilder
Expand All @@ -18,7 +18,11 @@ module Data.Double.Conversion.Internal.ByteStringBuilder

import Control.Monad (when)

#if MIN_VERSION_bytestring(0,10,12)
import Data.ByteString.Builder.Prim.Internal (BoundedPrim, boundedPrim)
#else
import Data.ByteString.Builder.Prim.Internal (BoundedPrim, boudedPrim)
#endif

import Data.Double.Conversion.Internal.FFI (ForeignFloating)
import Data.Word (Word8)
Expand All @@ -29,7 +33,11 @@ convert :: (RealFloat a, RealFloat b , b ~ ForeignFloating a) => String -> CInt
{-# SPECIALIZE convert :: String -> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double #-}
{-# SPECIALIZE convert :: String -> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float #-}
{-# INLINABLE convert #-}
#if MIN_VERSION_bytestring(0,10,12)
convert func len act = boundedPrim (fromIntegral len) $ \val ptr -> do
#else
convert func len act = boudedPrim (fromIntegral len) $ \val ptr -> do
#endif
size <- act (realToFrac val) ptr
when (size == -1) .
fail $ "Data.Double.Conversion.ByteString." ++ func ++
Expand Down
5 changes: 5 additions & 0 deletions Data/Double/Conversion/Internal/FFI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,12 @@ import Foreign.C.Types (CDouble, CFloat, CInt)
import Foreign.Ptr (Ptr)
import GHC.Prim (MutableByteArray#)

#if __GLASGOW_HASKELL__ >= 906
import Data.Kind (Type)
type family ForeignFloating h :: Type
#else
type family ForeignFloating h :: *

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.0.2 on ubuntu-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.2.8 on ubuntu-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.4.7 on ubuntu-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.0.2 on macos-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.2.8 on macos-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’

Check warning on line 54 in Data/Double/Conversion/Internal/FFI.hs

View workflow job for this annotation

GitHub Actions / 9.4.7 on macos-latest

Using ‘*’ (or its Unicode variant) to mean ‘Data.Kind.Type’
#endif

type instance ForeignFloating Double = CDouble
type instance ForeignFloating Float = CFloat
Expand Down

0 comments on commit 52c3ba6

Please sign in to comment.