{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Effectful.Concurrent.Static
(
Concurrent,
labelThread,
#if MIN_VERSION_base(4, 18, 0)
threadLabel,
#endif
microsleep,
sleep,
Natural,
)
where
import Control.Concurrent (ThreadId)
import Data.Foldable (for_)
import Effectful (Eff, type (:>))
import Effectful.Concurrent (Concurrent)
import Effectful.Concurrent qualified as EffCC
import Effectful.Dispatch.Static (HasCallStack, unsafeEff_)
import GHC.Conc.Sync qualified as Sync
import GHC.Natural (Natural)
labelThread ::
(Concurrent :> es, HasCallStack) =>
ThreadId ->
String ->
Eff es ()
labelThread :: forall (es :: [Effect]).
(Concurrent :> es, HasCallStack) =>
ThreadId -> String -> Eff es ()
labelThread ThreadId
tid = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (String -> IO ()) -> String -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreadId -> String -> IO ()
Sync.labelThread ThreadId
tid
#if MIN_VERSION_base(4, 18, 0)
threadLabel ::
(Concurrent :> es, HasCallStack) =>
ThreadId -> Eff es (Maybe String)
threadLabel :: forall (es :: [Effect]).
(Concurrent :> es, HasCallStack) =>
ThreadId -> Eff es (Maybe String)
threadLabel = IO (Maybe String) -> Eff es (Maybe String)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe String) -> Eff es (Maybe String))
-> (ThreadId -> IO (Maybe String))
-> ThreadId
-> Eff es (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThreadId -> IO (Maybe String)
Sync.threadLabel
#endif
microsleep :: (Concurrent :> es, HasCallStack) => Natural -> Eff es ()
microsleep :: forall (es :: [Effect]).
(Concurrent :> es, HasCallStack) =>
Natural -> Eff es ()
microsleep Natural
n = [Int] -> (Int -> Eff es ()) -> Eff es ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (Natural -> [Int]
natToInts Natural
n) Int -> Eff es ()
forall (es :: [Effect]). (Concurrent :> es) => Int -> Eff es ()
EffCC.threadDelay
sleep :: (Concurrent :> es, HasCallStack) => Natural -> Eff es ()
sleep :: forall (es :: [Effect]).
(Concurrent :> es, HasCallStack) =>
Natural -> Eff es ()
sleep = Natural -> Eff es ()
forall (es :: [Effect]).
(Concurrent :> es, HasCallStack) =>
Natural -> Eff es ()
microsleep (Natural -> Eff es ())
-> (Natural -> Natural) -> Natural -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
* Natural
1_000_000)
natToInts :: Natural -> [Int]
natToInts :: Natural -> [Int]
natToInts Natural
n
| Natural
n Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
maxIntAsNat = Int
maxInt Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Natural -> [Int]
natToInts (Natural
n Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
maxIntAsNat)
| Bool
otherwise = [Natural -> Int
n2i Natural
n]
where
maxInt :: Int
maxInt :: Int
maxInt = Int
forall a. Bounded a => a
maxBound
maxIntAsNat :: Natural
maxIntAsNat :: Natural
maxIntAsNat = Int -> Natural
i2n Int
maxInt
n2i :: Natural -> Int
n2i :: Natural -> Int
n2i = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
i2n :: Int -> Natural
i2n :: Int -> Natural
i2n = Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral