From 6c58d7f29dcd48b2888e5fd6da805c176d38193f Mon Sep 17 00:00:00 2001
From: konsumlamm <konsumlamm@gmail.com>
Date: Thu, 7 Sep 2023 01:01:41 +0200
Subject: [PATCH] Fix strictness of `stateTVar`

---
 Control/Concurrent/STM/TVar.hs | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/Control/Concurrent/STM/TVar.hs b/Control/Concurrent/STM/TVar.hs
index bf451e1..a1a65c7 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 #-}
-- 
GitLab