Skip to content
Snippets Groups Projects
Commit fe18b9b0 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

TArray: Don't rely on undefined CPP behavior

Fixes #75.
parent 92b80b26
No related branches found
No related tags found
No related merge requests found
......@@ -4,9 +4,11 @@
{-# LANGUAGE Trustworthy #-}
#endif
#define HAS_UNLIFTED_ARRAY defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 904
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 904
#define HAS_UNLIFTED_ARRAY 1
#endif
#if HAS_UNLIFTED_ARRAY
#if defined(HAS_UNLIFTED_ARRAY)
{-# LANGUAGE MagicHash, UnboxedTuples #-}
#endif
......@@ -30,7 +32,7 @@ module Control.Concurrent.STM.TArray (
import Control.Monad.STM (STM, atomically)
import Data.Typeable (Typeable)
#if HAS_UNLIFTED_ARRAY
#if defined(HAS_UNLIFTED_ARRAY)
import Control.Concurrent.STM.TVar (readTVar, readTVarIO, writeTVar)
import Data.Array.Base (safeRangeSize, MArray(..))
import Data.Ix (Ix)
......@@ -47,7 +49,7 @@ import Data.Array.Base (safeRangeSize, unsafeAt, MArray(..), IArray(numElements)
-- interface for mutable arrays.
--
-- It is conceptually implemented as @Array i (TVar e)@.
#if HAS_UNLIFTED_ARRAY
#if defined(HAS_UNLIFTED_ARRAY)
data TArray i e = TArray
!i -- lower bound
!i -- upper bound
......
# Changelog for [`stm` package](http://hackage.haskell.org/package/stm)
## 2.5.2.1 *September 2023*
* Eliminate reliance on undefined CPP behavior ([#75](https://github.com/haskell/stm/issues/75))
## 2.5.2.0 *September 2023*
* Fix strictness of `stateTVar` ([#30](https://github.com/haskell/stm/ssues/30))
......
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