diff --git a/Control/Concurrent/STM/TVar.hs b/Control/Concurrent/STM/TVar.hs index bf451e17dd971a22814c49c33a64bfe1ee6dabdd..a1a65c75bba065c8f6c41f60661fdb27b14f1c1a 100644 --- a/Control/Concurrent/STM/TVar.hs +++ b/Control/Concurrent/STM/TVar.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-} #if __GLASGOW_HASKELL__ >= 701 {-# LANGUAGE Trustworthy #-} @@ -73,7 +73,7 @@ modifyTVar' var f = do stateTVar :: TVar s -> (s -> (a, s)) -> STM a stateTVar var f = do s <- readTVar var - let (a, s') = f s -- since we destructure this, we are strict in f + let !(a, s') = f s writeTVar var s' return a {-# INLINE stateTVar #-}