Skip to content

Commit

Permalink
Use GHC2024 and GHC2021 extensions
Browse files Browse the repository at this point in the history
  • Loading branch information
harendra-kumar committed Feb 19, 2025
1 parent 4e2fccb commit 5540eae
Show file tree
Hide file tree
Showing 7 changed files with 67 additions and 18 deletions.
11 changes: 11 additions & 0 deletions benchmark/streamly-benchmarks.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,17 @@ flag use-prelude
-------------------------------------------------------------------------------

common default-extensions
-- GHC2024 may include more extensions than we are actually using, see the
-- full list below. We enable this to ensure that we are able to compile
-- with this i.e. there is no interference by other extensions.
if impl(ghc >= 9.10)
default-extensions:
GHC2024

if impl(ghc >= 9.2) && impl(ghc < 9.10)
default-extensions:
GHC2021

default-extensions:
BangPatterns
CApiFFI
Expand Down
13 changes: 7 additions & 6 deletions core/src/Streamly/Internal/FileSystem/File.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ where

import Control.Monad.Catch (MonadCatch)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Kind (Type)
import Data.Word (Word8)
import System.IO (Handle, openFile, IOMode(..), hClose)
import Prelude hiding (read)
Expand Down Expand Up @@ -204,15 +205,15 @@ usingFile3 = UF.bracketIO before after
-- /Pre-release/
--
{-# INLINABLE putChunk #-}
putChunk :: FilePath -> Array a -> IO ()
putChunk :: forall (a :: Type). FilePath -> Array a -> IO ()
putChunk file arr = SIO.withFile file WriteMode (`FH.putChunk` arr)

-- | append an array to a file.
--
-- /Pre-release/
--
{-# INLINABLE writeAppendArray #-}
writeAppendArray :: FilePath -> Array a -> IO ()
writeAppendArray :: forall (a :: Type). FilePath -> Array a -> IO ()
writeAppendArray file arr = SIO.withFile file AppendMode (`FH.putChunk` arr)

-------------------------------------------------------------------------------
Expand Down Expand Up @@ -369,7 +370,7 @@ readShared = undefined
-------------------------------------------------------------------------------

{-# INLINE fromChunksMode #-}
fromChunksMode :: (MonadIO m, MonadCatch m)
fromChunksMode :: forall m (a :: Type). (MonadIO m, MonadCatch m)
=> IOMode -> FilePath -> Stream m (Array a) -> m ()
fromChunksMode mode file xs = S.fold drain $
withFile file mode (\h -> S.mapM (FH.putChunk h) xs)
Expand All @@ -379,7 +380,7 @@ fromChunksMode mode file xs = S.fold drain $
-- /Pre-release/
--
{-# INLINE fromChunks #-}
fromChunks :: (MonadIO m, MonadCatch m)
fromChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m)
=> FilePath -> Stream m (Array a) -> m ()
fromChunks = fromChunksMode WriteMode

Expand Down Expand Up @@ -431,7 +432,7 @@ write = toHandleWith A.defaultChunkSize
--
-- /Pre-release/
{-# INLINE writeChunks #-}
writeChunks :: (MonadIO m, MonadCatch m)
writeChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m)
=> FilePath -> Fold m (Array a) ()
writeChunks path = Fold step initial extract final
where
Expand Down Expand Up @@ -487,7 +488,7 @@ write = writeWith defaultChunkSize
-- /Pre-release/
--
{-# INLINE writeAppendChunks #-}
writeAppendChunks :: (MonadIO m, MonadCatch m)
writeAppendChunks :: forall m (a :: Type). (MonadIO m, MonadCatch m)
=> FilePath -> Stream m (Array a) -> m ()
writeAppendChunks = fromChunksMode AppendMode

Expand Down
10 changes: 6 additions & 4 deletions core/src/Streamly/Internal/FileSystem/Handle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,7 @@ where
import Control.Exception (assert)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Function ((&))
import Data.Kind (Type)
import Data.Maybe (isNothing, fromJust)
import Data.Word (Word8)
import Streamly.Internal.Data.Unbox (Unbox)
Expand Down Expand Up @@ -373,7 +374,7 @@ read = A.concat . readChunks
-- | Write an 'Array' to a file handle.
--
{-# INLINABLE putChunk #-}
putChunk :: MonadIO m => Handle -> Array a -> m ()
putChunk :: forall m (a :: Type). MonadIO m => Handle -> Array a -> m ()
putChunk _ arr | byteLength arr == 0 = return ()
putChunk h arr = A.unsafePinnedAsPtr arr $ \ptr byteLen ->
liftIO $ hPutBuf h ptr byteLen
Expand All @@ -392,7 +393,8 @@ putChunk h arr = A.unsafePinnedAsPtr arr $ \ptr byteLen ->
-- >>> putChunks h = Stream.fold (Fold.drainBy (Handle.putChunk h))
--
{-# INLINE putChunks #-}
putChunks :: MonadIO m => Handle -> Stream m (Array a) -> m ()
putChunks :: forall m (a :: Type). MonadIO m =>
Handle -> Stream m (Array a) -> m ()
putChunks h = S.fold (FL.drainMapM (putChunk h))

-- XXX AS.compact can be written idiomatically in terms of foldMany, just like
Expand Down Expand Up @@ -437,14 +439,14 @@ putBytes = putBytesWith defaultChunkSize
-- writeChunks h = Fold.drainBy (Handle.putChunk h)
--
{-# INLINE writeChunks #-}
writeChunks :: MonadIO m => Handle -> Fold m (Array a) ()
writeChunks :: forall m (a :: Type). MonadIO m => Handle -> Fold m (Array a) ()
writeChunks h = FL.drainMapM (putChunk h)

-- | Like writeChunks but uses the experimental 'Refold' API.
--
-- /Internal/
{-# INLINE chunkWriter #-}
chunkWriter :: MonadIO m => Refold m Handle (Array a) ()
chunkWriter :: forall m (a :: Type). MonadIO m => Refold m Handle (Array a) ()
chunkWriter = Refold.drainBy putChunk

-- | @writeChunksWith bufsize handle@ writes a stream of arrays
Expand Down
16 changes: 14 additions & 2 deletions core/streamly-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -214,6 +214,18 @@ common compile-options
cpp-options: -DUSE_UNLIFTIO

common default-extensions
-- GHC2024 may include more extensions than we are actually using, see the
-- full list below. We enable this to ensure that we are able to compile
-- with this i.e. there is no interference by other extensions.
if impl(ghc >= 9.10)
default-extensions:
GHC2024

if impl(ghc >= 9.2) && impl(ghc < 9.10)
default-extensions:
GHC2021

-- In GHC 2024
default-extensions:
BangPatterns
ConstraintKinds
Expand All @@ -226,6 +238,7 @@ common default-extensions
GeneralizedNewtypeDeriving
InstanceSigs
KindSignatures
LambdaCase
MultiParamTypeClasses
RankNTypes
ScopedTypeVariables
Expand All @@ -234,11 +247,10 @@ common default-extensions
TypeApplications
TypeOperators

-- Not GHC2021
-- Not in GHC2024
CApiFFI
CPP
DefaultSignatures
LambdaCase
MagicHash
RecordWildCards

Expand Down
7 changes: 3 additions & 4 deletions src/Streamly/Internal/Data/Stream/IsStream/Reduce.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1604,8 +1604,7 @@ classifySessionsOf = classifySessionsBy 1 False
--
-- /Pre-release/
{-# INLINE splitInnerBy #-}
splitInnerBy
:: (IsStream t, Monad m)
splitInnerBy :: forall t m (f :: Type -> Type) a. (IsStream t, Monad m)
=> (f a -> m (f a, Maybe (f a))) -- splitter
-> (f a -> f a -> m (f a)) -- joiner
-> t m (f a)
Expand All @@ -1618,8 +1617,8 @@ splitInnerBy splitter joiner xs =
--
-- /Pre-release/
{-# INLINE splitInnerBySuffix #-}
splitInnerBySuffix
:: (IsStream t, Monad m, Eq (f a), Monoid (f a))
splitInnerBySuffix :: forall t m (f :: Type -> Type) a.
(IsStream t, Monad m, Eq (f a), Monoid (f a))
=> (f a -> m (f a, Maybe (f a))) -- splitter
-> (f a -> f a -> m (f a)) -- joiner
-> t m (f a)
Expand Down
17 changes: 15 additions & 2 deletions streamly.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -297,6 +297,18 @@ common compile-options
cpp-options: -DUSE_UNLIFTIO

common default-extensions
-- GHC2024 may include more extensions than we are actually using, see the
-- full list below. We enable this to ensure that we are able to compile
-- with this i.e. there is no interference by other extensions.
if impl(ghc >= 9.10)
default-extensions:
GHC2024

if impl(ghc >= 9.2) && impl(ghc < 9.10)
default-extensions:
GHC2021

-- In GHC 2024
default-extensions:
BangPatterns
ConstraintKinds
Expand All @@ -309,17 +321,18 @@ common default-extensions
GeneralizedNewtypeDeriving
InstanceSigs
KindSignatures
LambdaCase
MultiParamTypeClasses
RankNTypes
ScopedTypeVariables
TupleSections
TypeApplications
TypeOperators

-- Not GHC2021
-- Not in GHC2024
default-extensions:
CApiFFI
CPP
LambdaCase
MagicHash
RecordWildCards

Expand Down
11 changes: 11 additions & 0 deletions test/streamly-tests.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,17 @@ common compile-options
cpp-options: -DINCLUDE_FLAKY_TESTS

common default-extensions
-- GHC2024 may include more extensions than we are actually using, see the
-- full list below. We enable this to ensure that we are able to compile
-- with this i.e. there is no interference by other extensions.
if impl(ghc >= 9.10)
default-extensions:
GHC2024

if impl(ghc >= 9.2) && impl(ghc < 9.10)
default-extensions:
GHC2021

default-extensions:
BangPatterns
CApiFFI
Expand Down

0 comments on commit 5540eae

Please sign in to comment.