From ee8b926ab8dd2d03ddcd78a6fb55526ed2968249 Mon Sep 17 00:00:00 2001 From: Ryan Trinkle Date: Mon, 10 Apr 2023 22:32:12 -0400 Subject: [PATCH] Minor cleanups --- src/Test/UIO.hs | 2 +- src/UIO.hs | 38 +++++++++++--------------------------- 2 files changed, 12 insertions(+), 28 deletions(-) diff --git a/src/Test/UIO.hs b/src/Test/UIO.hs index 3e568be..b9f2d3d 100644 --- a/src/Test/UIO.hs +++ b/src/Test/UIO.hs @@ -1,5 +1,5 @@ {-# LANGUAGE RecursiveDo #-} -{-# OPTIONS_GHC -fplugin UIO.Plugin #-} +{-# OPTIONS_GHC -fplugin UIO #-} module Test.UIO where import Data.IORef diff --git a/src/UIO.hs b/src/UIO.hs index d265a6b..d74faca 100644 --- a/src/UIO.hs +++ b/src/UIO.hs @@ -1,33 +1,18 @@ {-# LANGUAGE MagicHash #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE UnboxedTuples #-} -{-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE RecursiveDo #-} -module UIO where +module UIO + ( module UIO + , module X + ) where -import System.Mem -import System.Mem.Weak -import Data.IORef -import GHC.IORef -import GHC.STRef -import GHC.IO -import GHC.Weak -import GHC.Prim -import Control.Monad.Primitive -import Data.IntMap.Strict (IntMap) -import qualified Data.IntMap.Strict as IntMap -import Data.Set (Set) -import qualified Data.Set as Set -import System.IO.Unsafe -import Control.Monad -import Control.Concurrent -import Data.Foldable -import Data.These -import Unsafe.Coerce import Control.Monad.Fix -import Data.List.NonEmpty (NonEmpty (..)) +import Data.Foldable import Data.Semigroup -import GHC.Magic +import GHC.IO +import GHC.Prim + +import UIO.Plugin as X data RemainingWork = RemainingWork @@ -55,7 +40,7 @@ instance Applicative UIO2 where {-# INLINE pure #-} {-# INLINE (*>) #-} {-# INLINE (<*>) #-} - pure x = UIO2 (\s -> (RemainingWork, x)) + pure x = UIO2 (\_ -> (RemainingWork, x)) UIO2 m *> UIO2 k = UIO2 (\s -> let (ms, _) = m (uniqueState 1# s) (ks, b) = k (uniqueState 2# s) @@ -75,6 +60,7 @@ instance Monad UIO2 where in (ms <> ks, b)) instance MonadFix UIO2 where + {-# INLINE mfix #-} mfix k = UIO2 (\s -> let (ks, result) = unUIO2 (k result) s in (ks, result)) @@ -103,5 +89,3 @@ uniqueState = uniqueState' {-# NOINLINE uniqueState' #-} uniqueState' :: Int# -> State# RealWorld -> State# RealWorld uniqueState' _ s = s --- This implementation seems to work sometimes, but I don't understand why, and it seems highly dependent on other aspects of the implementation. --- uniqueState = runRW# (\s _ _ -> s)