Skip to content
Snippets Groups Projects
Commit 13553fc6 authored by Jens Nolte's avatar Jens Nolte
Browse files

Rename unreachableCodePath

parent 93cccac9
No related branches found
No related tags found
No related merge requests found
Pipeline #2523 failed
......@@ -327,7 +327,7 @@ instance MonadFix AwaitableStepM where
result <- fn $ unsafeDupablePerformIO do
atomically (readTMVar var) `catch` \BlockedIndefinitelyOnSTM -> throwIO FixAwaitException
storeResult var result
applyFix (Left _) = impossibleCodePathM -- `newEmptyTMVar` should never fail
applyFix (Left _) = unreachableCodePathM -- `newEmptyTMVar` should never fail
storeResult :: TMVar a -> a -> AwaitableStepM a
storeResult var x = AwaitableStep (void $ tryPutTMVar var x) (\_ -> pure x)
......@@ -464,7 +464,7 @@ awaitAny xs = mkMonadicAwaitable $ stepAll Empty Empty $ runAwaitable <$> fromLi
do prevSteps |> step
steps
stepAll acc _ Empty = do
newAwaitableSteps <- unsafeAwaitSTM $ maybe impossibleCodePathM anySTM $ nonEmpty (toList acc)
newAwaitableSteps <- unsafeAwaitSTM $ maybe unreachableCodePathM anySTM $ nonEmpty (toList acc)
stepAll Empty Empty newAwaitableSteps
-- | Helper for `awaitAny`
......
......@@ -126,7 +126,7 @@ instance Exception ObserveWhileCompleted
-- | Observe until the callback returns `Just`.
observeWhile :: (IsObservable v o, MonadResourceManager m) => o -> (ObservableMessage v -> m (Maybe a)) -> m a
observeWhile observable callback = do
resultVar <- liftIO $ newIORef impossibleCodePath
resultVar <- liftIO $ newIORef unreachableCodePath
observeWhile_ observable \msg -> do
callback msg >>= \case
Just result -> do
......
......@@ -22,11 +22,19 @@ import Quasar.Utils.ExtraT
io :: IO a -> IO a
io = id
unreachableCodePath :: GHC.Stack.Types.HasCallStack => a
unreachableCodePath = error "Code path marked as unreachable was reached"
impossibleCodePath :: GHC.Stack.Types.HasCallStack => a
impossibleCodePath = error "Code path marked as impossible was reached"
{-# DEPRECATED impossibleCodePath "Use unreachableCodePath instead" #-}
unreachableCodePathM :: MonadThrow m => m a
unreachableCodePathM = throwM (userError "Code path marked as unreachable was reached")
impossibleCodePathM :: MonadThrow m => m a
impossibleCodePathM = throwM (userError "Code path marked as impossible was reached")
{-# DEPRECATED impossibleCodePathM "Use unreachableCodePathM instead" #-}
intercalate :: (Foldable f, Monoid a) => a -> f a -> a
intercalate inter = foldr1 (\a b -> a <> inter <> b)
......
......@@ -37,7 +37,7 @@ instance IsDisposable (Task r) where
beginDispose self@(Task key stateVar _ _) = uninterruptibleMask_ do
join $ atomically do
readTVar stateVar >>= \case
TaskStateInitializing -> impossibleCodePathM
TaskStateInitializing -> unreachableCodePathM
TaskStateRunning threadId -> do
writeTVar stateVar TaskStateThrowing
pure do
......
......@@ -32,7 +32,7 @@ spec = parallel $ do
describe "subscribe" $ do
it "calls the callback with the contents of the map" $ io $ withRootResourceManager do
lastCallbackValue <- liftIO $ newIORef impossibleCodePath
lastCallbackValue <- liftIO $ newIORef unreachableCodePath
om :: OM.ObservableHashMap String String <- OM.new
subscriptionHandle <- captureDisposable_ $ observe om $ liftIO . writeIORef lastCallbackValue
......@@ -54,7 +54,7 @@ spec = parallel $ do
describe "subscribeDelta" $ do
it "calls the callback with changes to the map" $ io $ withRootResourceManager do
lastDelta <- liftIO $ newIORef impossibleCodePath
lastDelta <- liftIO $ newIORef unreachableCodePath
om :: OM.ObservableHashMap String String <- OM.new
subscriptionHandle <- subscribeDelta om $ writeIORef lastDelta
......
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