Cheng Shao pushed to branch wip/T25365 at Glasgow Haskell Compiler / GHC
Commits:
-
d9ea5841
by Ben Gamari at 2026-01-09T02:10:54+01:00
-
60a30360
by Ben Gamari at 2026-01-09T02:11:01+01:00
-
0916ed4e
by Ben Gamari at 2026-01-09T02:11:01+01:00
16 changed files:
- libraries/base/changelog.md
- libraries/base/src/GHC/Conc.hs
- libraries/base/src/GHC/Conc/Sync.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- + libraries/ghc-internal/src/GHC/Internal/STM.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
| ... | ... | @@ -17,6 +17,8 @@ |
| 17 | 17 | * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
|
| 18 | 18 | * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
|
| 19 | 19 | * Add `Semigroup` and `Monoid` instances for `Control.Monad.ST.Lazy`. ([CLC proposal #374](https://github.com/haskell/core-libraries-committee/issues/374))
|
| 20 | + * `GHC.Conc.throwSTM` and `GHC.Conc.Sync.throwSTM` now carry a `HasCallStack` constraint and attach a `Backtrace` annotation to the thrown exception. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365))
|
|
| 21 | + * `GHC.Conc.catchSTM` and `GHC.Conc.Sync.catchSTM` now attach `WhileHandling` annotation to exceptions thrown from the handler. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365))
|
|
| 20 | 22 | |
| 21 | 23 | ## 4.22.0.0 *TBA*
|
| 22 | 24 | * Shipped with GHC 9.14.1
|
| ... | ... | @@ -119,6 +119,7 @@ module GHC.Conc |
| 119 | 119 | |
| 120 | 120 | import GHC.Internal.Conc.IO
|
| 121 | 121 | import GHC.Internal.Conc.Sync
|
| 122 | +import GHC.Internal.STM
|
|
| 122 | 123 | |
| 123 | 124 | #if !defined(mingw32_HOST_OS)
|
| 124 | 125 | import GHC.Internal.Conc.Signal
|
| ... | ... | @@ -89,3 +89,4 @@ module GHC.Conc.Sync |
| 89 | 89 | ) where
|
| 90 | 90 | |
| 91 | 91 | import GHC.Internal.Conc.Sync
|
| 92 | +import GHC.Internal.STM |
| ... | ... | @@ -293,6 +293,7 @@ Library |
| 293 | 293 | GHC.Internal.StaticPtr
|
| 294 | 294 | GHC.Internal.STRef
|
| 295 | 295 | GHC.Internal.Show
|
| 296 | + GHC.Internal.STM
|
|
| 296 | 297 | GHC.Internal.Stable
|
| 297 | 298 | GHC.Internal.StableName
|
| 298 | 299 | GHC.Internal.Stack
|
| ... | ... | @@ -60,6 +60,7 @@ module GHC.Internal.Conc.IO |
| 60 | 60 | |
| 61 | 61 | import GHC.Internal.Base
|
| 62 | 62 | import GHC.Internal.Conc.Sync as Sync
|
| 63 | +import GHC.Internal.STM as STM
|
|
| 63 | 64 | import GHC.Internal.Real ( fromIntegral )
|
| 64 | 65 | import GHC.Internal.System.Posix.Types
|
| 65 | 66 | |
| ... | ... | @@ -142,17 +143,17 @@ threadWaitWrite fd |
| 142 | 143 | -- to read from a file descriptor. The second returned value
|
| 143 | 144 | -- is an IO action that can be used to deregister interest
|
| 144 | 145 | -- in the file descriptor.
|
| 145 | -threadWaitReadSTM :: Fd -> IO (Sync.STM (), IO ())
|
|
| 146 | +threadWaitReadSTM :: Fd -> IO (STM.STM (), IO ())
|
|
| 146 | 147 | threadWaitReadSTM fd
|
| 147 | 148 | #if !defined(mingw32_HOST_OS) && !defined(javascript_HOST_ARCH)
|
| 148 | 149 | | threaded = Event.threadWaitReadSTM fd
|
| 149 | 150 | #endif
|
| 150 | 151 | | otherwise = do
|
| 151 | - m <- Sync.newTVarIO False
|
|
| 152 | + m <- STM.newTVarIO False
|
|
| 152 | 153 | t <- Sync.forkIO $ do
|
| 153 | 154 | threadWaitRead fd
|
| 154 | - Sync.atomically $ Sync.writeTVar m True
|
|
| 155 | - let waitAction = do b <- Sync.readTVar m
|
|
| 155 | + STM.atomically $ STM.writeTVar m True
|
|
| 156 | + let waitAction = do b <- STM.readTVar m
|
|
| 156 | 157 | if b then return () else retry
|
| 157 | 158 | let killAction = Sync.killThread t
|
| 158 | 159 | return (waitAction, killAction)
|
| ... | ... | @@ -161,17 +162,17 @@ threadWaitReadSTM fd |
| 161 | 162 | -- can be written to a file descriptor. The second returned value
|
| 162 | 163 | -- is an IO action that can be used to deregister interest
|
| 163 | 164 | -- in the file descriptor.
|
| 164 | -threadWaitWriteSTM :: Fd -> IO (Sync.STM (), IO ())
|
|
| 165 | +threadWaitWriteSTM :: Fd -> IO (STM.STM (), IO ())
|
|
| 165 | 166 | threadWaitWriteSTM fd
|
| 166 | 167 | #if !defined(mingw32_HOST_OS) && !defined(javascript_HOST_ARCH)
|
| 167 | 168 | | threaded = Event.threadWaitWriteSTM fd
|
| 168 | 169 | #endif
|
| 169 | 170 | | otherwise = do
|
| 170 | - m <- Sync.newTVarIO False
|
|
| 171 | + m <- STM.newTVarIO False
|
|
| 171 | 172 | t <- Sync.forkIO $ do
|
| 172 | 173 | threadWaitWrite fd
|
| 173 | - Sync.atomically $ Sync.writeTVar m True
|
|
| 174 | - let waitAction = do b <- Sync.readTVar m
|
|
| 174 | + STM.atomically $ STM.writeTVar m True
|
|
| 175 | + let waitAction = do b <- STM.readTVar m
|
|
| 175 | 176 | if b then return () else retry
|
| 176 | 177 | let killAction = Sync.killThread t
|
| 177 | 178 | return (waitAction, killAction)
|
| ... | ... | @@ -56,6 +56,7 @@ import GHC.Internal.MVar |
| 56 | 56 | import GHC.Internal.Num (Num(..))
|
| 57 | 57 | import GHC.Internal.Ptr
|
| 58 | 58 | import GHC.Internal.Real (div, fromIntegral)
|
| 59 | +import GHC.Internal.STM (TVar, atomically, newTVar, writeTVar)
|
|
| 59 | 60 | import GHC.Internal.Word (Word32, Word64)
|
| 60 | 61 | import GHC.Internal.Windows
|
| 61 | 62 |
| ... | ... | @@ -76,21 +76,6 @@ module GHC.Internal.Conc.Sync |
| 76 | 76 | , enableAllocationLimit
|
| 77 | 77 | , disableAllocationLimit
|
| 78 | 78 | |
| 79 | - -- * TVars
|
|
| 80 | - , STM(..)
|
|
| 81 | - , atomically
|
|
| 82 | - , retry
|
|
| 83 | - , orElse
|
|
| 84 | - , throwSTM
|
|
| 85 | - , catchSTM
|
|
| 86 | - , TVar(..)
|
|
| 87 | - , newTVar
|
|
| 88 | - , newTVarIO
|
|
| 89 | - , readTVar
|
|
| 90 | - , readTVarIO
|
|
| 91 | - , writeTVar
|
|
| 92 | - , unsafeIOToSTM
|
|
| 93 | - |
|
| 94 | 79 | -- * Miscellaneous
|
| 95 | 80 | , withMVar
|
| 96 | 81 | , modifyMVar_
|
| ... | ... | @@ -665,220 +650,6 @@ mkWeakThreadId t@(ThreadId t#) = IO $ \s -> |
| 665 | 650 | (# s1, w #) -> (# s1, Weak w #)
|
| 666 | 651 | |
| 667 | 652 | |
| 668 | ------------------------------------------------------------------------------
|
|
| 669 | --- Transactional heap operations
|
|
| 670 | ------------------------------------------------------------------------------
|
|
| 671 | - |
|
| 672 | --- TVars are shared memory locations which support atomic memory
|
|
| 673 | --- transactions.
|
|
| 674 | - |
|
| 675 | --- |A monad supporting atomic memory transactions.
|
|
| 676 | -newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #))
|
|
| 677 | - |
|
| 678 | -unSTM :: STM a -> (State# RealWorld -> (# State# RealWorld, a #))
|
|
| 679 | -unSTM (STM a) = a
|
|
| 680 | - |
|
| 681 | --- | @since base-4.3.0.0
|
|
| 682 | -instance Functor STM where
|
|
| 683 | - fmap f x = x >>= (pure . f)
|
|
| 684 | - |
|
| 685 | --- | @since base-4.8.0.0
|
|
| 686 | -instance Applicative STM where
|
|
| 687 | - {-# INLINE pure #-}
|
|
| 688 | - {-# INLINE (*>) #-}
|
|
| 689 | - {-# INLINE liftA2 #-}
|
|
| 690 | - pure x = returnSTM x
|
|
| 691 | - (<*>) = ap
|
|
| 692 | - liftA2 = liftM2
|
|
| 693 | - m *> k = thenSTM m k
|
|
| 694 | - |
|
| 695 | --- | @since base-4.3.0.0
|
|
| 696 | -instance Monad STM where
|
|
| 697 | - {-# INLINE (>>=) #-}
|
|
| 698 | - m >>= k = bindSTM m k
|
|
| 699 | - (>>) = (*>)
|
|
| 700 | - |
|
| 701 | --- | @since base-4.17.0.0
|
|
| 702 | -instance Semigroup a => Semigroup (STM a) where
|
|
| 703 | - (<>) = liftA2 (<>)
|
|
| 704 | - |
|
| 705 | --- | @since base-4.17.0.0
|
|
| 706 | -instance Monoid a => Monoid (STM a) where
|
|
| 707 | - mempty = pure mempty
|
|
| 708 | - |
|
| 709 | -bindSTM :: STM a -> (a -> STM b) -> STM b
|
|
| 710 | -bindSTM (STM m) k = STM ( \s ->
|
|
| 711 | - case m s of
|
|
| 712 | - (# new_s, a #) -> unSTM (k a) new_s
|
|
| 713 | - )
|
|
| 714 | - |
|
| 715 | -thenSTM :: STM a -> STM b -> STM b
|
|
| 716 | -thenSTM (STM m) k = STM ( \s ->
|
|
| 717 | - case m s of
|
|
| 718 | - (# new_s, _ #) -> unSTM k new_s
|
|
| 719 | - )
|
|
| 720 | - |
|
| 721 | -returnSTM :: a -> STM a
|
|
| 722 | -returnSTM x = STM (\s -> (# s, x #))
|
|
| 723 | - |
|
| 724 | --- | Takes the first non-'retry'ing 'STM' action.
|
|
| 725 | ---
|
|
| 726 | --- @since base-4.8.0.0
|
|
| 727 | -instance Alternative STM where
|
|
| 728 | - empty = retry
|
|
| 729 | - (<|>) = orElse
|
|
| 730 | - |
|
| 731 | --- | Takes the first non-'retry'ing 'STM' action.
|
|
| 732 | ---
|
|
| 733 | --- @since base-4.3.0.0
|
|
| 734 | -instance MonadPlus STM
|
|
| 735 | - |
|
| 736 | --- | Unsafely performs IO in the STM monad. Beware: this is a highly
|
|
| 737 | --- dangerous thing to do.
|
|
| 738 | ---
|
|
| 739 | --- * The STM implementation will often run transactions multiple
|
|
| 740 | --- times, so you need to be prepared for this if your IO has any
|
|
| 741 | --- side effects.
|
|
| 742 | ---
|
|
| 743 | --- * The STM implementation will abort transactions that are known to
|
|
| 744 | --- be invalid and need to be restarted. This may happen in the middle
|
|
| 745 | --- of `unsafeIOToSTM`, so make sure you don't acquire any resources
|
|
| 746 | --- that need releasing (exception handlers are ignored when aborting
|
|
| 747 | --- the transaction). That includes doing any IO using Handles, for
|
|
| 748 | --- example. Getting this wrong will probably lead to random deadlocks.
|
|
| 749 | ---
|
|
| 750 | --- * The transaction may have seen an inconsistent view of memory when
|
|
| 751 | --- the IO runs. Invariants that you expect to be true throughout
|
|
| 752 | --- your program may not be true inside a transaction, due to the
|
|
| 753 | --- way transactions are implemented. Normally this wouldn't be visible
|
|
| 754 | --- to the programmer, but using `unsafeIOToSTM` can expose it.
|
|
| 755 | ---
|
|
| 756 | -unsafeIOToSTM :: IO a -> STM a
|
|
| 757 | -unsafeIOToSTM (IO m) = STM m
|
|
| 758 | - |
|
| 759 | --- | Perform a series of STM actions atomically.
|
|
| 760 | ---
|
|
| 761 | --- Using 'atomically' inside an 'unsafePerformIO' or 'unsafeInterleaveIO'
|
|
| 762 | --- subverts some of guarantees that STM provides. It makes it possible to
|
|
| 763 | --- run a transaction inside of another transaction, depending on when the
|
|
| 764 | --- thunk is evaluated. If a nested transaction is attempted, an exception
|
|
| 765 | --- is thrown by the runtime. It is possible to safely use 'atomically' inside
|
|
| 766 | --- 'unsafePerformIO' or 'unsafeInterleaveIO', but the typechecker does not
|
|
| 767 | --- rule out programs that may attempt nested transactions, meaning that
|
|
| 768 | --- the programmer must take special care to prevent these.
|
|
| 769 | ---
|
|
| 770 | --- However, there are functions for creating transactional variables that
|
|
| 771 | --- can always be safely called in 'unsafePerformIO'. See: 'newTVarIO',
|
|
| 772 | --- 'Control.Concurrent.STM.TChan.newTChanIO',
|
|
| 773 | --- 'Control.Concurrent.STM.TChan.newBroadcastTChanIO',
|
|
| 774 | --- 'Control.Concurrent.STM.TQueue.newTQueueIO',
|
|
| 775 | --- 'Control.Concurrent.STM.TBQueue.newTBQueueIO', and
|
|
| 776 | --- 'Control.Concurrent.STM.TMVar.newTMVarIO'.
|
|
| 777 | ---
|
|
| 778 | --- Using 'unsafePerformIO' inside of 'atomically' is also dangerous but for
|
|
| 779 | --- different reasons. See 'unsafeIOToSTM' for more on this.
|
|
| 780 | - |
|
| 781 | -atomically :: STM a -> IO a
|
|
| 782 | -atomically (STM m) = IO (\s -> (atomically# m) s )
|
|
| 783 | - |
|
| 784 | --- | Retry execution of the current memory transaction because it has seen
|
|
| 785 | --- values in 'TVar's which mean that it should not continue (e.g. the 'TVar's
|
|
| 786 | --- represent a shared buffer that is now empty). The implementation may
|
|
| 787 | --- block the thread until one of the 'TVar's that it has read from has been
|
|
| 788 | --- updated. (GHC only)
|
|
| 789 | -retry :: STM a
|
|
| 790 | -retry = STM $ \s# -> retry# s#
|
|
| 791 | - |
|
| 792 | --- | Compose two alternative STM actions (GHC only).
|
|
| 793 | ---
|
|
| 794 | --- If the first action completes without retrying then it forms the result of
|
|
| 795 | --- the 'orElse'. Otherwise, if the first action retries, then the second action
|
|
| 796 | --- is tried in its place. If both actions retry then the 'orElse' as a whole
|
|
| 797 | --- retries.
|
|
| 798 | -orElse :: STM a -> STM a -> STM a
|
|
| 799 | -orElse (STM m) e = STM $ \s -> catchRetry# m (unSTM e) s
|
|
| 800 | - |
|
| 801 | --- | A variant of 'throw' that can only be used within the 'STM' monad.
|
|
| 802 | ---
|
|
| 803 | --- Throwing an exception in @STM@ aborts the transaction and propagates the
|
|
| 804 | --- exception. If the exception is caught via 'catchSTM', only the changes
|
|
| 805 | --- enclosed by the catch are rolled back; changes made outside of 'catchSTM'
|
|
| 806 | --- persist.
|
|
| 807 | ---
|
|
| 808 | --- If the exception is not caught inside of the 'STM', it is re-thrown by
|
|
| 809 | --- 'atomically', and the entire 'STM' is rolled back.
|
|
| 810 | ---
|
|
| 811 | --- Although 'throwSTM' has a type that is an instance of the type of 'throw', the
|
|
| 812 | --- two functions are subtly different:
|
|
| 813 | ---
|
|
| 814 | --- > throw e `seq` x ===> throw e
|
|
| 815 | --- > throwSTM e `seq` x ===> x
|
|
| 816 | ---
|
|
| 817 | --- The first example will cause the exception @e@ to be raised,
|
|
| 818 | --- whereas the second one won\'t. In fact, 'throwSTM' will only cause
|
|
| 819 | --- an exception to be raised when it is used within the 'STM' monad.
|
|
| 820 | --- The 'throwSTM' variant should be used in preference to 'throw' to
|
|
| 821 | --- raise an exception within the 'STM' monad because it guarantees
|
|
| 822 | --- ordering with respect to other 'STM' operations, whereas 'throw'
|
|
| 823 | --- does not.
|
|
| 824 | -throwSTM :: Exception e => e -> STM a
|
|
| 825 | -throwSTM e = STM $ raiseIO# (toException e)
|
|
| 826 | - |
|
| 827 | --- | Exception handling within STM actions.
|
|
| 828 | ---
|
|
| 829 | --- @'catchSTM' m f@ catches any exception thrown by @m@ using 'throwSTM',
|
|
| 830 | --- using the function @f@ to handle the exception. If an exception is
|
|
| 831 | --- thrown, any changes made by @m@ are rolled back, but changes prior to
|
|
| 832 | --- @m@ persist.
|
|
| 833 | -catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
|
|
| 834 | -catchSTM (STM m) handler = STM $ catchSTM# m handler'
|
|
| 835 | - where
|
|
| 836 | - handler' e = case fromException e of
|
|
| 837 | - Just e' -> unSTM (handler e')
|
|
| 838 | - Nothing -> raiseIO# e
|
|
| 839 | - |
|
| 840 | --- |Shared memory locations that support atomic memory transactions.
|
|
| 841 | -data TVar a = TVar (TVar# RealWorld a)
|
|
| 842 | - |
|
| 843 | --- | @since base-4.8.0.0
|
|
| 844 | -instance Eq (TVar a) where
|
|
| 845 | - (TVar tvar1#) == (TVar tvar2#) = isTrue# (sameTVar# tvar1# tvar2#)
|
|
| 846 | - |
|
| 847 | --- | Create a new 'TVar' holding a value supplied
|
|
| 848 | -newTVar :: a -> STM (TVar a)
|
|
| 849 | -newTVar val = STM $ \s1# ->
|
|
| 850 | - case newTVar# val s1# of
|
|
| 851 | - (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
|
|
| 852 | - |
|
| 853 | --- | @IO@ version of 'newTVar'. This is useful for creating top-level
|
|
| 854 | --- 'TVar's using 'System.IO.Unsafe.unsafePerformIO', because using
|
|
| 855 | --- 'atomically' inside 'System.IO.Unsafe.unsafePerformIO' isn't
|
|
| 856 | --- possible.
|
|
| 857 | -newTVarIO :: a -> IO (TVar a)
|
|
| 858 | -newTVarIO val = IO $ \s1# ->
|
|
| 859 | - case newTVar# val s1# of
|
|
| 860 | - (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
|
|
| 861 | - |
|
| 862 | --- | Return the current value stored in a 'TVar'.
|
|
| 863 | --- This is equivalent to
|
|
| 864 | ---
|
|
| 865 | --- > readTVarIO = atomically . readTVar
|
|
| 866 | ---
|
|
| 867 | --- but works much faster, because it doesn't perform a complete
|
|
| 868 | --- transaction, it just reads the current value of the 'TVar'.
|
|
| 869 | -readTVarIO :: TVar a -> IO a
|
|
| 870 | -readTVarIO (TVar tvar#) = IO $ \s# -> readTVarIO# tvar# s#
|
|
| 871 | - |
|
| 872 | --- |Return the current value stored in a 'TVar'.
|
|
| 873 | -readTVar :: TVar a -> STM a
|
|
| 874 | -readTVar (TVar tvar#) = STM $ \s# -> readTVar# tvar# s#
|
|
| 875 | - |
|
| 876 | --- |Write the supplied value into a 'TVar'.
|
|
| 877 | -writeTVar :: TVar a -> a -> STM ()
|
|
| 878 | -writeTVar (TVar tvar#) val = STM $ \s1# ->
|
|
| 879 | - case writeTVar# tvar# val s1# of
|
|
| 880 | - s2# -> (# s2#, () #)
|
|
| 881 | - |
|
| 882 | 653 | -----------------------------------------------------------------------------
|
| 883 | 654 | -- MVar utilities
|
| 884 | 655 | -----------------------------------------------------------------------------
|
| ... | ... | @@ -17,7 +17,6 @@ |
| 17 | 17 | |
| 18 | 18 | module GHC.Internal.Conc.Sync
|
| 19 | 19 | ( forkIO,
|
| 20 | - TVar(..),
|
|
| 21 | 20 | ThreadId(..),
|
| 22 | 21 | myThreadId,
|
| 23 | 22 | showThreadId,
|
| ... | ... | @@ -33,7 +32,6 @@ import GHC.Internal.Ptr |
| 33 | 32 | forkIO :: IO () -> IO ThreadId
|
| 34 | 33 | |
| 35 | 34 | data ThreadId = ThreadId ThreadId#
|
| 36 | -data TVar a = TVar (TVar# RealWorld a)
|
|
| 37 | 35 | |
| 38 | 36 | data BlockReason
|
| 39 | 37 | = BlockedOnMVar
|
| ... | ... | @@ -42,12 +42,12 @@ module GHC.Internal.Conc.Windows |
| 42 | 42 | ) where
|
| 43 | 43 | |
| 44 | 44 | import GHC.Internal.Base
|
| 45 | -import GHC.Internal.Conc.Sync
|
|
| 46 | 45 | import qualified GHC.Internal.Conc.POSIX as POSIX
|
| 47 | 46 | import qualified GHC.Internal.Event.Windows.Thread as WINIO
|
| 48 | 47 | import GHC.Internal.Event.Windows.ConsoleEvent
|
| 49 | 48 | import GHC.Internal.IO.SubSystem ((<!>))
|
| 50 | 49 | import GHC.Internal.Ptr
|
| 50 | +import GHC.Internal.STM
|
|
| 51 | 51 | |
| 52 | 52 | -- ----------------------------------------------------------------------------
|
| 53 | 53 | -- Thread waiting
|
| ... | ... | @@ -38,11 +38,11 @@ import GHC.Internal.Foreign.C.Types (CInt(..), CUInt(..)) |
| 38 | 38 | import GHC.Internal.Foreign.Ptr (Ptr)
|
| 39 | 39 | import GHC.Internal.Base
|
| 40 | 40 | import GHC.Internal.List (zipWith, zipWith3)
|
| 41 | -import GHC.Internal.Conc.Sync (TVar, ThreadId, ThreadStatus(..), atomically, forkIO,
|
|
| 42 | - labelThread, modifyMVar_, withMVar, newTVar, sharedCAF,
|
|
| 41 | +import GHC.Internal.STM (TVar, atomically, newTVar, writeTVar, newTVarIO, readTVar, retry, throwSTM, STM)
|
|
| 42 | +import GHC.Internal.Conc.Sync (ThreadId, ThreadStatus(..), forkIO,
|
|
| 43 | + labelThread, modifyMVar_, withMVar, sharedCAF,
|
|
| 43 | 44 | getNumCapabilities, threadCapability, myThreadId, forkOn,
|
| 44 | - threadStatus, writeTVar, newTVarIO, readTVar, retry,
|
|
| 45 | - throwSTM, STM, yield)
|
|
| 45 | + threadStatus, yield)
|
|
| 46 | 46 | import GHC.Internal.IO (mask_, uninterruptibleMask_, onException)
|
| 47 | 47 | import GHC.Internal.IO.Exception (ioError)
|
| 48 | 48 | import GHC.Internal.IOArray (IOArray, newIOArray, readIOArray, writeIOArray,
|
| ... | ... | @@ -7,11 +7,11 @@ module GHC.Internal.Event.Windows.Thread ( |
| 7 | 7 | registerDelay,
|
| 8 | 8 | ) where
|
| 9 | 9 | |
| 10 | -import GHC.Internal.Conc.Sync
|
|
| 11 | 10 | import GHC.Internal.Base
|
| 12 | 11 | import GHC.Internal.Event.Windows
|
| 13 | 12 | import GHC.Internal.IO
|
| 14 | 13 | import GHC.Internal.MVar
|
| 14 | +import GHC.Internal.STM
|
|
| 15 | 15 | |
| 16 | 16 | ensureIOManagerIsRunning :: IO ()
|
| 17 | 17 | ensureIOManagerIsRunning = wakeupIOManager
|
| ... | ... | @@ -36,4 +36,3 @@ registerDelay usecs = do |
| 36 | 36 | mgr <- getSystemManager
|
| 37 | 37 | _ <- registerTimeout mgr usecs $ atomically $ writeTVar t True
|
| 38 | 38 | return t |
| 39 | - |
| 1 | +{-# LANGUAGE NoImplicitPrelude #-}
|
|
| 2 | +{-# LANGUAGE UnboxedTuples #-}
|
|
| 3 | +{-# LANGUAGE MagicHash #-}
|
|
| 4 | +{-# LANGUAGE GADTs #-}
|
|
| 5 | +{-# LANGUAGE RankNTypes #-}
|
|
| 6 | +{-# OPTIONS_HADDOCK not-home #-}
|
|
| 7 | + |
|
| 8 | +module GHC.Internal.STM
|
|
| 9 | + (
|
|
| 10 | + -- * the 'STM' monad
|
|
| 11 | + STM(..)
|
|
| 12 | + , atomically
|
|
| 13 | + , retry
|
|
| 14 | + , orElse
|
|
| 15 | + , throwSTM
|
|
| 16 | + , catchSTM
|
|
| 17 | + , unsafeIOToSTM
|
|
| 18 | + -- * TVars
|
|
| 19 | + , TVar(..)
|
|
| 20 | + , newTVar
|
|
| 21 | + , newTVarIO
|
|
| 22 | + , readTVar
|
|
| 23 | + , readTVarIO
|
|
| 24 | + , writeTVar
|
|
| 25 | + ) where
|
|
| 26 | + |
|
| 27 | +import GHC.Internal.Base
|
|
| 28 | +import GHC.Internal.Exception (Exception, toExceptionWithBacktrace, fromException, addExceptionContext)
|
|
| 29 | +import GHC.Internal.Exception.Context (ExceptionAnnotation)
|
|
| 30 | +import GHC.Internal.Exception.Type (WhileHandling(..))
|
|
| 31 | +import GHC.Internal.Stack (HasCallStack)
|
|
| 32 | + |
|
| 33 | +-- TVars are shared memory locations which support atomic memory
|
|
| 34 | +-- transactions.
|
|
| 35 | + |
|
| 36 | +-- |A monad supporting atomic memory transactions.
|
|
| 37 | +newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #))
|
|
| 38 | + |
|
| 39 | +unSTM :: STM a -> (State# RealWorld -> (# State# RealWorld, a #))
|
|
| 40 | +unSTM (STM a) = a
|
|
| 41 | + |
|
| 42 | +-- | @since base-4.3.0.0
|
|
| 43 | +instance Functor STM where
|
|
| 44 | + fmap f x = x >>= (pure . f)
|
|
| 45 | + |
|
| 46 | +-- | @since base-4.8.0.0
|
|
| 47 | +instance Applicative STM where
|
|
| 48 | + {-# INLINE pure #-}
|
|
| 49 | + {-# INLINE (*>) #-}
|
|
| 50 | + {-# INLINE liftA2 #-}
|
|
| 51 | + pure x = returnSTM x
|
|
| 52 | + (<*>) = ap
|
|
| 53 | + liftA2 = liftM2
|
|
| 54 | + m *> k = thenSTM m k
|
|
| 55 | + |
|
| 56 | +-- | @since base-4.3.0.0
|
|
| 57 | +instance Monad STM where
|
|
| 58 | + {-# INLINE (>>=) #-}
|
|
| 59 | + m >>= k = bindSTM m k
|
|
| 60 | + (>>) = (*>)
|
|
| 61 | + |
|
| 62 | +-- | @since base-4.17.0.0
|
|
| 63 | +instance Semigroup a => Semigroup (STM a) where
|
|
| 64 | + (<>) = liftA2 (<>)
|
|
| 65 | + |
|
| 66 | +-- | @since base-4.17.0.0
|
|
| 67 | +instance Monoid a => Monoid (STM a) where
|
|
| 68 | + mempty = pure mempty
|
|
| 69 | + |
|
| 70 | +bindSTM :: STM a -> (a -> STM b) -> STM b
|
|
| 71 | +bindSTM (STM m) k = STM ( \s ->
|
|
| 72 | + case m s of
|
|
| 73 | + (# new_s, a #) -> unSTM (k a) new_s
|
|
| 74 | + )
|
|
| 75 | + |
|
| 76 | +thenSTM :: STM a -> STM b -> STM b
|
|
| 77 | +thenSTM (STM m) k = STM ( \s ->
|
|
| 78 | + case m s of
|
|
| 79 | + (# new_s, _ #) -> unSTM k new_s
|
|
| 80 | + )
|
|
| 81 | + |
|
| 82 | +returnSTM :: a -> STM a
|
|
| 83 | +returnSTM x = STM (\s -> (# s, x #))
|
|
| 84 | + |
|
| 85 | +-- | Takes the first non-'retry'ing 'STM' action.
|
|
| 86 | +--
|
|
| 87 | +-- @since base-4.8.0.0
|
|
| 88 | +instance Alternative STM where
|
|
| 89 | + empty = retry
|
|
| 90 | + (<|>) = orElse
|
|
| 91 | + |
|
| 92 | +-- | Takes the first non-'retry'ing 'STM' action.
|
|
| 93 | +--
|
|
| 94 | +-- @since base-4.3.0.0
|
|
| 95 | +instance MonadPlus STM
|
|
| 96 | + |
|
| 97 | +-- | Unsafely performs IO in the STM monad. Beware: this is a highly
|
|
| 98 | +-- dangerous thing to do.
|
|
| 99 | +--
|
|
| 100 | +-- * The STM implementation will often run transactions multiple
|
|
| 101 | +-- times, so you need to be prepared for this if your IO has any
|
|
| 102 | +-- side effects.
|
|
| 103 | +--
|
|
| 104 | +-- * The STM implementation will abort transactions that are known to
|
|
| 105 | +-- be invalid and need to be restarted. This may happen in the middle
|
|
| 106 | +-- of `unsafeIOToSTM`, so make sure you don't acquire any resources
|
|
| 107 | +-- that need releasing (exception handlers are ignored when aborting
|
|
| 108 | +-- the transaction). That includes doing any IO using Handles, for
|
|
| 109 | +-- example. Getting this wrong will probably lead to random deadlocks.
|
|
| 110 | +--
|
|
| 111 | +-- * The transaction may have seen an inconsistent view of memory when
|
|
| 112 | +-- the IO runs. Invariants that you expect to be true throughout
|
|
| 113 | +-- your program may not be true inside a transaction, due to the
|
|
| 114 | +-- way transactions are implemented. Normally this wouldn't be visible
|
|
| 115 | +-- to the programmer, but using `unsafeIOToSTM` can expose it.
|
|
| 116 | +--
|
|
| 117 | +unsafeIOToSTM :: IO a -> STM a
|
|
| 118 | +unsafeIOToSTM (IO m) = STM m
|
|
| 119 | + |
|
| 120 | +-- | Perform a series of STM actions atomically.
|
|
| 121 | +--
|
|
| 122 | +-- Using 'atomically' inside an 'unsafePerformIO' or 'unsafeInterleaveIO'
|
|
| 123 | +-- subverts some of guarantees that STM provides. It makes it possible to
|
|
| 124 | +-- run a transaction inside of another transaction, depending on when the
|
|
| 125 | +-- thunk is evaluated. If a nested transaction is attempted, an exception
|
|
| 126 | +-- is thrown by the runtime. It is possible to safely use 'atomically' inside
|
|
| 127 | +-- 'unsafePerformIO' or 'unsafeInterleaveIO', but the typechecker does not
|
|
| 128 | +-- rule out programs that may attempt nested transactions, meaning that
|
|
| 129 | +-- the programmer must take special care to prevent these.
|
|
| 130 | +--
|
|
| 131 | +-- However, there are functions for creating transactional variables that
|
|
| 132 | +-- can always be safely called in 'unsafePerformIO'. See: 'newTVarIO',
|
|
| 133 | +-- 'Control.Concurrent.STM.TChan.newTChanIO',
|
|
| 134 | +-- 'Control.Concurrent.STM.TChan.newBroadcastTChanIO',
|
|
| 135 | +-- 'Control.Concurrent.STM.TQueue.newTQueueIO',
|
|
| 136 | +-- 'Control.Concurrent.STM.TBQueue.newTBQueueIO', and
|
|
| 137 | +-- 'Control.Concurrent.STM.TMVar.newTMVarIO'.
|
|
| 138 | +--
|
|
| 139 | +-- Using 'unsafePerformIO' inside of 'atomically' is also dangerous but for
|
|
| 140 | +-- different reasons. See 'unsafeIOToSTM' for more on this.
|
|
| 141 | + |
|
| 142 | +atomically :: STM a -> IO a
|
|
| 143 | +atomically (STM m) = IO (\s -> (atomically# m) s )
|
|
| 144 | + |
|
| 145 | +-- | Retry execution of the current memory transaction because it has seen
|
|
| 146 | +-- values in 'TVar's which mean that it should not continue (e.g. the 'TVar's
|
|
| 147 | +-- represent a shared buffer that is now empty). The implementation may
|
|
| 148 | +-- block the thread until one of the 'TVar's that it has read from has been
|
|
| 149 | +-- updated. (GHC only)
|
|
| 150 | +retry :: STM a
|
|
| 151 | +retry = STM $ \s# -> retry# s#
|
|
| 152 | + |
|
| 153 | +-- | Compose two alternative STM actions (GHC only).
|
|
| 154 | +--
|
|
| 155 | +-- If the first action completes without retrying then it forms the result of
|
|
| 156 | +-- the 'orElse'. Otherwise, if the first action retries, then the second action
|
|
| 157 | +-- is tried in its place. If both actions retry then the 'orElse' as a whole
|
|
| 158 | +-- retries.
|
|
| 159 | +orElse :: STM a -> STM a -> STM a
|
|
| 160 | +orElse (STM m) e = STM $ \s -> catchRetry# m (unSTM e) s
|
|
| 161 | + |
|
| 162 | +-- | A variant of 'throw' that can only be used within the 'STM' monad.
|
|
| 163 | +--
|
|
| 164 | +-- Throwing an exception in @STM@ aborts the transaction and propagates the
|
|
| 165 | +-- exception. If the exception is caught via 'catchSTM', only the changes
|
|
| 166 | +-- enclosed by the catch are rolled back; changes made outside of 'catchSTM'
|
|
| 167 | +-- persist.
|
|
| 168 | +--
|
|
| 169 | +-- If the exception is not caught inside of the 'STM', it is re-thrown by
|
|
| 170 | +-- 'atomically', and the entire 'STM' is rolled back.
|
|
| 171 | +--
|
|
| 172 | +-- Although 'throwSTM' has a type that is an instance of the type of 'throw', the
|
|
| 173 | +-- two functions are subtly different:
|
|
| 174 | +--
|
|
| 175 | +-- > throw e `seq` x ===> throw e
|
|
| 176 | +-- > throwSTM e `seq` x ===> x
|
|
| 177 | +--
|
|
| 178 | +-- The first example will cause the exception @e@ to be raised,
|
|
| 179 | +-- whereas the second one won\'t. In fact, 'throwSTM' will only cause
|
|
| 180 | +-- an exception to be raised when it is used within the 'STM' monad.
|
|
| 181 | +-- The 'throwSTM' variant should be used in preference to 'throw' to
|
|
| 182 | +-- raise an exception within the 'STM' monad because it guarantees
|
|
| 183 | +-- ordering with respect to other 'STM' operations, whereas 'throw'
|
|
| 184 | +-- does not.
|
|
| 185 | +throwSTM :: (HasCallStack, Exception e) => e -> STM a
|
|
| 186 | +throwSTM e = do
|
|
| 187 | + -- N.B. Typically use of unsafeIOToSTM is very much frowned upon as this
|
|
| 188 | + -- is an easy way to end up with nested transactions. However, we can be
|
|
| 189 | + -- certain that toExceptionWithBacktrace will not initiate a transaction.
|
|
| 190 | + se <- unsafeIOToSTM (toExceptionWithBacktrace e)
|
|
| 191 | + STM $ raiseIO# se
|
|
| 192 | + |
|
| 193 | +-- | Exception handling within STM actions.
|
|
| 194 | +--
|
|
| 195 | +-- @'catchSTM' m f@ catches any exception thrown by @m@ using 'throwSTM',
|
|
| 196 | +-- using the function @f@ to handle the exception. If an exception is
|
|
| 197 | +-- thrown, any changes made by @m@ are rolled back, but changes prior to
|
|
| 198 | +-- @m@ persist.
|
|
| 199 | +catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
|
|
| 200 | +catchSTM (STM m) handler = STM $ catchSTM# m handler'
|
|
| 201 | + where
|
|
| 202 | + handler' e = case fromException e of
|
|
| 203 | + Just e' -> unSTM (annotateSTM (WhileHandling e) (handler e'))
|
|
| 204 | + Nothing -> raiseIO# e
|
|
| 205 | + |
|
| 206 | +-- | Execute an 'STM' action, adding the given 'ExceptionContext'
|
|
| 207 | +-- to any thrown synchronous exceptions.
|
|
| 208 | +annotateSTM :: forall e a. ExceptionAnnotation e => e -> STM a -> STM a
|
|
| 209 | +annotateSTM ann (STM io) = STM (catch# io handler)
|
|
| 210 | + where
|
|
| 211 | + handler se = raiseIO# (addExceptionContext ann se)
|
|
| 212 | + |
|
| 213 | +-- |Shared memory locations that support atomic memory transactions.
|
|
| 214 | +data TVar a = TVar (TVar# RealWorld a)
|
|
| 215 | + |
|
| 216 | +-- | @since base-4.8.0.0
|
|
| 217 | +instance Eq (TVar a) where
|
|
| 218 | + (TVar tvar1#) == (TVar tvar2#) = isTrue# (sameTVar# tvar1# tvar2#)
|
|
| 219 | + |
|
| 220 | +-- | Create a new 'TVar' holding a value supplied
|
|
| 221 | +newTVar :: a -> STM (TVar a)
|
|
| 222 | +newTVar val = STM $ \s1# ->
|
|
| 223 | + case newTVar# val s1# of
|
|
| 224 | + (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
|
|
| 225 | + |
|
| 226 | +-- | @IO@ version of 'newTVar'. This is useful for creating top-level
|
|
| 227 | +-- 'TVar's using 'System.IO.Unsafe.unsafePerformIO', because using
|
|
| 228 | +-- 'atomically' inside 'System.IO.Unsafe.unsafePerformIO' isn't
|
|
| 229 | +-- possible.
|
|
| 230 | +newTVarIO :: a -> IO (TVar a)
|
|
| 231 | +newTVarIO val = IO $ \s1# ->
|
|
| 232 | + case newTVar# val s1# of
|
|
| 233 | + (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
|
|
| 234 | + |
|
| 235 | +-- | Return the current value stored in a 'TVar'.
|
|
| 236 | +-- This is equivalent to
|
|
| 237 | +--
|
|
| 238 | +-- > readTVarIO = atomically . readTVar
|
|
| 239 | +--
|
|
| 240 | +-- but works much faster, because it doesn't perform a complete
|
|
| 241 | +-- transaction, it just reads the current value of the 'TVar'.
|
|
| 242 | +readTVarIO :: TVar a -> IO a
|
|
| 243 | +readTVarIO (TVar tvar#) = IO $ \s# -> readTVarIO# tvar# s#
|
|
| 244 | + |
|
| 245 | +-- |Return the current value stored in a 'TVar'.
|
|
| 246 | +readTVar :: TVar a -> STM a
|
|
| 247 | +readTVar (TVar tvar#) = STM $ \s# -> readTVar# tvar# s#
|
|
| 248 | + |
|
| 249 | +-- |Write the supplied value into a 'TVar'.
|
|
| 250 | +writeTVar :: TVar a -> a -> STM ()
|
|
| 251 | +writeTVar (TVar tvar#) val = STM $ \s1# ->
|
|
| 252 | + case writeTVar# tvar# val s1# of
|
|
| 253 | + s2# -> (# s2#, () #)
|
|
| 254 | + |
| ... | ... | @@ -146,9 +146,9 @@ module Control.Concurrent where |
| 146 | 146 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 147 | 147 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 148 | 148 | threadWaitRead :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 149 | - threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 149 | + threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 150 | 150 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 151 | - threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 151 | + threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 152 | 152 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 153 | 153 | tryPutMVar :: forall a. MVar a -> a -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| 154 | 154 | tryReadMVar :: forall a. MVar a -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe a)
|
| ... | ... | @@ -5117,7 +5117,7 @@ module GHC.Conc where |
| 5117 | 5117 | threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5118 | 5118 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 5119 | 5119 | threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5120 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5120 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5121 | 5121 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5122 | 5122 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5123 | 5123 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -5197,7 +5197,7 @@ module GHC.Conc.Sync where |
| 5197 | 5197 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 5198 | 5198 | threadLabel :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
| 5199 | 5199 | threadStatus :: ThreadId -> GHC.Internal.Types.IO ThreadStatus
|
| 5200 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5200 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5201 | 5201 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5202 | 5202 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5203 | 5203 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -11117,12 +11117,12 @@ instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in |
| 11117 | 11117 | instance GHC.Internal.Base.Alternative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11118 | 11118 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowPlus a => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11119 | 11119 | instance forall (m :: * -> *) a. GHC.Internal.Base.Alternative m => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11120 | -instance GHC.Internal.Base.Alternative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11121 | 11120 | instance GHC.Internal.Base.Alternative GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11122 | 11121 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
|
| 11123 | 11122 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11124 | 11123 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11125 | 11124 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11125 | +instance GHC.Internal.Base.Alternative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11126 | 11126 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11127 | 11127 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11128 | 11128 | instance forall (f :: * -> *). (GHC.Internal.Generics.Generic1 f, GHC.Internal.Base.Alternative (GHC.Internal.Generics.Rep1 f)) => GHC.Internal.Base.Alternative (GHC.Internal.Generics.Generically1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11146,7 +11146,6 @@ instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Applicative ( |
| 11146 | 11146 | instance GHC.Internal.Base.Applicative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11147 | 11147 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11148 | 11148 | instance forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11149 | -instance GHC.Internal.Base.Applicative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11150 | 11149 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11151 | 11150 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11152 | 11151 | instance GHC.Internal.Base.Applicative Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11168,6 +11167,7 @@ instance GHC.Internal.Base.Applicative Data.Semigroup.First -- Defined in ‘Dat |
| 11168 | 11167 | instance GHC.Internal.Base.Applicative Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11169 | 11168 | instance GHC.Internal.Base.Applicative Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11170 | 11169 | instance GHC.Internal.Base.Applicative Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11170 | +instance GHC.Internal.Base.Applicative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11171 | 11171 | instance GHC.Internal.Base.Applicative GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11172 | 11172 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11173 | 11173 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11197,7 +11197,6 @@ instance forall m. GHC.Internal.Base.Functor (GHC.Internal.Data.Functor.Const.Co |
| 11197 | 11197 | instance GHC.Internal.Base.Functor GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11198 | 11198 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11199 | 11199 | instance forall (m :: * -> *) a. GHC.Internal.Base.Functor m => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11200 | -instance GHC.Internal.Base.Functor GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11201 | 11200 | instance GHC.Internal.Base.Functor GHC.Internal.Control.Exception.Handler -- Defined in ‘GHC.Internal.Control.Exception’
|
| 11202 | 11201 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11203 | 11202 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11223,6 +11222,7 @@ instance GHC.Internal.Base.Functor Data.Semigroup.Last -- Defined in ‘Data.Sem |
| 11223 | 11222 | instance GHC.Internal.Base.Functor Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11224 | 11223 | instance GHC.Internal.Base.Functor Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11225 | 11224 | instance forall i. GHC.Internal.Base.Functor (GHC.Internal.Arr.Array i) -- Defined in ‘GHC.Internal.Arr’
|
| 11225 | +instance GHC.Internal.Base.Functor GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11226 | 11226 | instance GHC.Internal.Base.Functor GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11227 | 11227 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11228 | 11228 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:+: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11257,7 +11257,6 @@ instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => |
| 11257 | 11257 | instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monad ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’
|
| 11258 | 11258 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowApply a => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11259 | 11259 | instance forall (m :: * -> *) a. GHC.Internal.Base.Monad m => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11260 | -instance GHC.Internal.Base.Monad GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11261 | 11260 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11262 | 11261 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11263 | 11262 | instance GHC.Internal.Base.Monad Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11278,6 +11277,7 @@ instance GHC.Internal.Base.Monad Data.Semigroup.First -- Defined in ‘Data.Semi |
| 11278 | 11277 | instance GHC.Internal.Base.Monad Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11279 | 11278 | instance GHC.Internal.Base.Monad Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11280 | 11279 | instance GHC.Internal.Base.Monad Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11280 | +instance GHC.Internal.Base.Monad GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11281 | 11281 | instance GHC.Internal.Base.Monad GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11282 | 11282 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Monad f, GHC.Internal.Base.Monad g) => GHC.Internal.Base.Monad (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11283 | 11283 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.Monad f => GHC.Internal.Base.Monad (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11292,11 +11292,11 @@ instance GHC.Internal.Base.MonadPlus [] -- Defined in ‘GHC.Internal.Base’ |
| 11292 | 11292 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
|
| 11293 | 11293 | instance forall (a :: * -> * -> *). (GHC.Internal.Control.Arrow.ArrowApply a, GHC.Internal.Control.Arrow.ArrowPlus a) => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11294 | 11294 | instance forall (m :: * -> *) a. GHC.Internal.Base.MonadPlus m => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11295 | -instance GHC.Internal.Base.MonadPlus GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11296 | 11295 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11297 | 11296 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11298 | 11297 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11299 | 11298 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11299 | +instance GHC.Internal.Base.MonadPlus GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11300 | 11300 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11301 | 11301 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| 11302 | 11302 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11316,7 +11316,6 @@ instance forall a b c d. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b |
| 11316 | 11316 | instance forall a b c d e. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d, GHC.Internal.Base.Monoid e) => GHC.Internal.Base.Monoid (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’
|
| 11317 | 11317 | instance GHC.Internal.Base.Monoid () -- Defined in ‘GHC.Internal.Base’
|
| 11318 | 11318 | instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11319 | -instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11320 | 11319 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11321 | 11320 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11322 | 11321 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11347,6 +11346,7 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I |
| 11347 | 11346 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11348 | 11347 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11349 | 11348 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11349 | +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11350 | 11350 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11351 | 11351 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11352 | 11352 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| ... | ... | @@ -11371,7 +11371,6 @@ instance forall a b c d e. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Sem |
| 11371 | 11371 | instance GHC.Internal.Base.Semigroup () -- Defined in ‘GHC.Internal.Base’
|
| 11372 | 11372 | instance GHC.Internal.Base.Semigroup GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
|
| 11373 | 11373 | instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11374 | -instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11375 | 11374 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11376 | 11375 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11377 | 11376 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11409,6 +11408,7 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define |
| 11409 | 11408 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11410 | 11409 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11411 | 11410 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11411 | +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11412 | 11412 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11413 | 11413 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11414 | 11414 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| ... | ... | @@ -11510,7 +11510,6 @@ instance forall a. GHC.Internal.Classes.Eq a => GHC.Internal.Classes.Eq (GHC.Int |
| 11510 | 11510 | instance forall a. GHC.Internal.Classes.Eq (Control.Concurrent.Chan.Chan a) -- Defined in ‘Control.Concurrent.Chan’
|
| 11511 | 11511 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.MVar.MVar a) -- Defined in ‘GHC.Internal.MVar’
|
| 11512 | 11512 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.BlockReason -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11513 | -instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Conc.Sync.TVar a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11514 | 11513 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadId -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11515 | 11514 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadStatus -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11516 | 11515 | instance GHC.Internal.Classes.Eq GHC.Internal.IO.Exception.ArrayException -- Defined in ‘GHC.Internal.IO.Exception’
|
| ... | ... | @@ -11640,6 +11639,7 @@ instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Foreign.C.ConstPtr.Cons |
| 11640 | 11639 | instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Internal.Classes.Eq e) => GHC.Internal.Classes.Eq (GHC.Internal.Arr.Array i e) -- Defined in ‘GHC.Internal.Arr’
|
| 11641 | 11640 | instance forall s i e. GHC.Internal.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
|
| 11642 | 11641 | instance GHC.Internal.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
|
| 11642 | +instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.STM.TVar a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11643 | 11643 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11644 | 11644 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11645 | 11645 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| ... | ... | @@ -146,9 +146,9 @@ module Control.Concurrent where |
| 146 | 146 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 147 | 147 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 148 | 148 | threadWaitRead :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 149 | - threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 149 | + threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 150 | 150 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 151 | - threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 151 | + threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 152 | 152 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 153 | 153 | tryPutMVar :: forall a. MVar a -> a -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| 154 | 154 | tryReadMVar :: forall a. MVar a -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe a)
|
| ... | ... | @@ -5117,7 +5117,7 @@ module GHC.Conc where |
| 5117 | 5117 | threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5118 | 5118 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 5119 | 5119 | threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5120 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5120 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5121 | 5121 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5122 | 5122 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5123 | 5123 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -5197,7 +5197,7 @@ module GHC.Conc.Sync where |
| 5197 | 5197 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 5198 | 5198 | threadLabel :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
| 5199 | 5199 | threadStatus :: ThreadId -> GHC.Internal.Types.IO ThreadStatus
|
| 5200 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5200 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5201 | 5201 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5202 | 5202 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5203 | 5203 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -14163,12 +14163,12 @@ instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in |
| 14163 | 14163 | instance GHC.Internal.Base.Alternative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 14164 | 14164 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowPlus a => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14165 | 14165 | instance forall (m :: * -> *) a. GHC.Internal.Base.Alternative m => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14166 | -instance GHC.Internal.Base.Alternative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14167 | 14166 | instance GHC.Internal.Base.Alternative GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 14168 | 14167 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
|
| 14169 | 14168 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 14170 | 14169 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 14171 | 14170 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 14171 | +instance GHC.Internal.Base.Alternative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 14172 | 14172 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14173 | 14173 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14174 | 14174 | instance forall (f :: * -> *). (GHC.Internal.Generics.Generic1 f, GHC.Internal.Base.Alternative (GHC.Internal.Generics.Rep1 f)) => GHC.Internal.Base.Alternative (GHC.Internal.Generics.Generically1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14192,7 +14192,6 @@ instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Applicative ( |
| 14192 | 14192 | instance GHC.Internal.Base.Applicative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 14193 | 14193 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14194 | 14194 | instance forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14195 | -instance GHC.Internal.Base.Applicative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14196 | 14195 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 14197 | 14196 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 14198 | 14197 | instance GHC.Internal.Base.Applicative Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -14214,6 +14213,7 @@ instance GHC.Internal.Base.Applicative Data.Semigroup.First -- Defined in ‘Dat |
| 14214 | 14213 | instance GHC.Internal.Base.Applicative Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 14215 | 14214 | instance GHC.Internal.Base.Applicative Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 14216 | 14215 | instance GHC.Internal.Base.Applicative Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 14216 | +instance GHC.Internal.Base.Applicative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 14217 | 14217 | instance GHC.Internal.Base.Applicative GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 14218 | 14218 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14219 | 14219 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14243,7 +14243,6 @@ instance forall m. GHC.Internal.Base.Functor (GHC.Internal.Data.Functor.Const.Co |
| 14243 | 14243 | instance GHC.Internal.Base.Functor GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 14244 | 14244 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14245 | 14245 | instance forall (m :: * -> *) a. GHC.Internal.Base.Functor m => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14246 | -instance GHC.Internal.Base.Functor GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14247 | 14246 | instance GHC.Internal.Base.Functor GHC.Internal.Control.Exception.Handler -- Defined in ‘GHC.Internal.Control.Exception’
|
| 14248 | 14247 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 14249 | 14248 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -14269,6 +14268,7 @@ instance GHC.Internal.Base.Functor Data.Semigroup.Last -- Defined in ‘Data.Sem |
| 14269 | 14268 | instance GHC.Internal.Base.Functor Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 14270 | 14269 | instance GHC.Internal.Base.Functor Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 14271 | 14270 | instance forall i. GHC.Internal.Base.Functor (GHC.Internal.Arr.Array i) -- Defined in ‘GHC.Internal.Arr’
|
| 14271 | +instance GHC.Internal.Base.Functor GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 14272 | 14272 | instance GHC.Internal.Base.Functor GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 14273 | 14273 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14274 | 14274 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:+: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14303,7 +14303,6 @@ instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => |
| 14303 | 14303 | instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monad ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’
|
| 14304 | 14304 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowApply a => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14305 | 14305 | instance forall (m :: * -> *) a. GHC.Internal.Base.Monad m => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14306 | -instance GHC.Internal.Base.Monad GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14307 | 14306 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 14308 | 14307 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 14309 | 14308 | instance GHC.Internal.Base.Monad Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -14324,6 +14323,7 @@ instance GHC.Internal.Base.Monad Data.Semigroup.First -- Defined in ‘Data.Semi |
| 14324 | 14323 | instance GHC.Internal.Base.Monad Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 14325 | 14324 | instance GHC.Internal.Base.Monad Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 14326 | 14325 | instance GHC.Internal.Base.Monad Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 14326 | +instance GHC.Internal.Base.Monad GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 14327 | 14327 | instance GHC.Internal.Base.Monad GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 14328 | 14328 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Monad f, GHC.Internal.Base.Monad g) => GHC.Internal.Base.Monad (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14329 | 14329 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.Monad f => GHC.Internal.Base.Monad (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14338,11 +14338,11 @@ instance GHC.Internal.Base.MonadPlus [] -- Defined in ‘GHC.Internal.Base’ |
| 14338 | 14338 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
|
| 14339 | 14339 | instance forall (a :: * -> * -> *). (GHC.Internal.Control.Arrow.ArrowApply a, GHC.Internal.Control.Arrow.ArrowPlus a) => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14340 | 14340 | instance forall (m :: * -> *) a. GHC.Internal.Base.MonadPlus m => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 14341 | -instance GHC.Internal.Base.MonadPlus GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14342 | 14341 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 14343 | 14342 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 14344 | 14343 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 14345 | 14344 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 14345 | +instance GHC.Internal.Base.MonadPlus GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 14346 | 14346 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 14347 | 14347 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| 14348 | 14348 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14362,7 +14362,6 @@ instance forall a b c d. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b |
| 14362 | 14362 | instance forall a b c d e. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d, GHC.Internal.Base.Monoid e) => GHC.Internal.Base.Monoid (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’
|
| 14363 | 14363 | instance GHC.Internal.Base.Monoid () -- Defined in ‘GHC.Internal.Base’
|
| 14364 | 14364 | instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 14365 | -instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14366 | 14365 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 14367 | 14366 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 14368 | 14367 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -14393,6 +14392,7 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I |
| 14393 | 14392 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 14394 | 14393 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 14395 | 14394 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 14395 | +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 14396 | 14396 | instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Monoid (f p), GHC.Internal.Base.Monoid (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 14397 | 14397 | instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Monoid (f (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 14398 | 14398 | instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Monoid (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Monoid (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14414,7 +14414,6 @@ instance forall a b c d e. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Sem |
| 14414 | 14414 | instance GHC.Internal.Base.Semigroup () -- Defined in ‘GHC.Internal.Base’
|
| 14415 | 14415 | instance GHC.Internal.Base.Semigroup GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
|
| 14416 | 14416 | instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 14417 | -instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14418 | 14417 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 14419 | 14418 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 14420 | 14419 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -14452,6 +14451,7 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define |
| 14452 | 14451 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 14453 | 14452 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 14454 | 14453 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 14454 | +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 14455 | 14455 | instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Semigroup (f p), GHC.Internal.Base.Semigroup (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 14456 | 14456 | instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Semigroup (f (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 14457 | 14457 | instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -14550,7 +14550,6 @@ instance forall a. GHC.Internal.Classes.Eq a => GHC.Internal.Classes.Eq (GHC.Int |
| 14550 | 14550 | instance forall a. GHC.Internal.Classes.Eq (Control.Concurrent.Chan.Chan a) -- Defined in ‘Control.Concurrent.Chan’
|
| 14551 | 14551 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.MVar.MVar a) -- Defined in ‘GHC.Internal.MVar’
|
| 14552 | 14552 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.BlockReason -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 14553 | -instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Conc.Sync.TVar a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 14554 | 14553 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadId -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 14555 | 14554 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadStatus -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 14556 | 14555 | instance GHC.Internal.Classes.Eq GHC.Internal.IO.Exception.ArrayException -- Defined in ‘GHC.Internal.IO.Exception’
|
| ... | ... | @@ -14680,6 +14679,7 @@ instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Foreign.C.ConstPtr.Cons |
| 14680 | 14679 | instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Internal.Classes.Eq e) => GHC.Internal.Classes.Eq (GHC.Internal.Arr.Array i e) -- Defined in ‘GHC.Internal.Arr’
|
| 14681 | 14680 | instance forall s i e. GHC.Internal.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
|
| 14682 | 14681 | instance GHC.Internal.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
|
| 14682 | +instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.STM.TVar a) -- Defined in ‘GHC.Internal.STM’
|
|
| 14683 | 14683 | instance GHC.Internal.Classes.Eq GHC.Internal.Event.TimeOut.TimeoutKey -- Defined in ‘GHC.Internal.Event.TimeOut’
|
| 14684 | 14684 | instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Types.SrcLoc -- Defined in ‘GHC.Internal.Stack.Types’
|
| 14685 | 14685 | instance GHC.Internal.Classes.Eq GHC.Internal.Exts.SpecConstrAnnotation -- Defined in ‘GHC.Internal.Exts’
|
| ... | ... | @@ -146,9 +146,9 @@ module Control.Concurrent where |
| 146 | 146 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 147 | 147 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 148 | 148 | threadWaitRead :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 149 | - threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 149 | + threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 150 | 150 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 151 | - threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 151 | + threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 152 | 152 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 153 | 153 | tryPutMVar :: forall a. MVar a -> a -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| 154 | 154 | tryReadMVar :: forall a. MVar a -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe a)
|
| ... | ... | @@ -5121,7 +5121,7 @@ module GHC.Conc where |
| 5121 | 5121 | threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5122 | 5122 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 5123 | 5123 | threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5124 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5124 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5125 | 5125 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5126 | 5126 | toWin32ConsoleEvent :: forall a. (GHC.Internal.Classes.Eq a, GHC.Internal.Num.Num a) => a -> GHC.Internal.Maybe.Maybe ConsoleEvent
|
| 5127 | 5127 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| ... | ... | @@ -5213,7 +5213,7 @@ module GHC.Conc.Sync where |
| 5213 | 5213 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 5214 | 5214 | threadLabel :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
| 5215 | 5215 | threadStatus :: ThreadId -> GHC.Internal.Types.IO ThreadStatus
|
| 5216 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5216 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5217 | 5217 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5218 | 5218 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5219 | 5219 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -5224,7 +5224,7 @@ module GHC.Conc.WinIO where |
| 5224 | 5224 | -- Safety: None
|
| 5225 | 5225 | ensureIOManagerIsRunning :: GHC.Internal.Types.IO ()
|
| 5226 | 5226 | interruptIOManager :: GHC.Internal.Types.IO ()
|
| 5227 | - registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.TVar GHC.Internal.Types.Bool)
|
|
| 5227 | + registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.STM.TVar GHC.Internal.Types.Bool)
|
|
| 5228 | 5228 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 5229 | 5229 | |
| 5230 | 5230 | module GHC.Conc.Windows where
|
| ... | ... | @@ -5238,7 +5238,7 @@ module GHC.Conc.Windows where |
| 5238 | 5238 | asyncWriteBA :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Int)
|
| 5239 | 5239 | ensureIOManagerIsRunning :: GHC.Internal.Types.IO ()
|
| 5240 | 5240 | interruptIOManager :: GHC.Internal.Types.IO ()
|
| 5241 | - registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.TVar GHC.Internal.Types.Bool)
|
|
| 5241 | + registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.STM.TVar GHC.Internal.Types.Bool)
|
|
| 5242 | 5242 | start_console_handler :: GHC.Internal.Word.Word32 -> GHC.Internal.Types.IO ()
|
| 5243 | 5243 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 5244 | 5244 | toWin32ConsoleEvent :: forall a. (GHC.Internal.Classes.Eq a, GHC.Internal.Num.Num a) => a -> GHC.Internal.Maybe.Maybe ConsoleEvent
|
| ... | ... | @@ -5445,7 +5445,7 @@ module GHC.Event.Windows.Thread where |
| 5445 | 5445 | -- Safety: None
|
| 5446 | 5446 | ensureIOManagerIsRunning :: GHC.Internal.Types.IO ()
|
| 5447 | 5447 | interruptIOManager :: GHC.Internal.Types.IO ()
|
| 5448 | - registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.TVar GHC.Internal.Types.Bool)
|
|
| 5448 | + registerDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO (GHC.Internal.STM.TVar GHC.Internal.Types.Bool)
|
|
| 5449 | 5449 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 5450 | 5450 | |
| 5451 | 5451 | module GHC.Exception where
|
| ... | ... | @@ -11379,12 +11379,12 @@ instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in |
| 11379 | 11379 | instance GHC.Internal.Base.Alternative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11380 | 11380 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowPlus a => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11381 | 11381 | instance forall (m :: * -> *) a. GHC.Internal.Base.Alternative m => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11382 | -instance GHC.Internal.Base.Alternative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11383 | 11382 | instance GHC.Internal.Base.Alternative GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11384 | 11383 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
|
| 11385 | 11384 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11386 | 11385 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11387 | 11386 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11387 | +instance GHC.Internal.Base.Alternative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11388 | 11388 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11389 | 11389 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11390 | 11390 | instance forall (f :: * -> *). (GHC.Internal.Generics.Generic1 f, GHC.Internal.Base.Alternative (GHC.Internal.Generics.Rep1 f)) => GHC.Internal.Base.Alternative (GHC.Internal.Generics.Generically1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11408,7 +11408,6 @@ instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Applicative ( |
| 11408 | 11408 | instance GHC.Internal.Base.Applicative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11409 | 11409 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11410 | 11410 | instance forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11411 | -instance GHC.Internal.Base.Applicative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11412 | 11411 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11413 | 11412 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11414 | 11413 | instance GHC.Internal.Base.Applicative Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11430,6 +11429,7 @@ instance GHC.Internal.Base.Applicative Data.Semigroup.First -- Defined in ‘Dat |
| 11430 | 11429 | instance GHC.Internal.Base.Applicative Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11431 | 11430 | instance GHC.Internal.Base.Applicative Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11432 | 11431 | instance GHC.Internal.Base.Applicative Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11432 | +instance GHC.Internal.Base.Applicative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11433 | 11433 | instance GHC.Internal.Base.Applicative GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11434 | 11434 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11435 | 11435 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11459,7 +11459,6 @@ instance forall m. GHC.Internal.Base.Functor (GHC.Internal.Data.Functor.Const.Co |
| 11459 | 11459 | instance GHC.Internal.Base.Functor GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11460 | 11460 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11461 | 11461 | instance forall (m :: * -> *) a. GHC.Internal.Base.Functor m => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11462 | -instance GHC.Internal.Base.Functor GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11463 | 11462 | instance GHC.Internal.Base.Functor GHC.Internal.Control.Exception.Handler -- Defined in ‘GHC.Internal.Control.Exception’
|
| 11464 | 11463 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11465 | 11464 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11485,6 +11484,7 @@ instance GHC.Internal.Base.Functor Data.Semigroup.Last -- Defined in ‘Data.Sem |
| 11485 | 11484 | instance GHC.Internal.Base.Functor Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11486 | 11485 | instance GHC.Internal.Base.Functor Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11487 | 11486 | instance forall i. GHC.Internal.Base.Functor (GHC.Internal.Arr.Array i) -- Defined in ‘GHC.Internal.Arr’
|
| 11487 | +instance GHC.Internal.Base.Functor GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11488 | 11488 | instance GHC.Internal.Base.Functor GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11489 | 11489 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11490 | 11490 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:+: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11519,7 +11519,6 @@ instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => |
| 11519 | 11519 | instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monad ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’
|
| 11520 | 11520 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowApply a => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11521 | 11521 | instance forall (m :: * -> *) a. GHC.Internal.Base.Monad m => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11522 | -instance GHC.Internal.Base.Monad GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11523 | 11522 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11524 | 11523 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11525 | 11524 | instance GHC.Internal.Base.Monad Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11540,6 +11539,7 @@ instance GHC.Internal.Base.Monad Data.Semigroup.First -- Defined in ‘Data.Semi |
| 11540 | 11539 | instance GHC.Internal.Base.Monad Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11541 | 11540 | instance GHC.Internal.Base.Monad Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11542 | 11541 | instance GHC.Internal.Base.Monad Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11542 | +instance GHC.Internal.Base.Monad GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11543 | 11543 | instance GHC.Internal.Base.Monad GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11544 | 11544 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Monad f, GHC.Internal.Base.Monad g) => GHC.Internal.Base.Monad (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11545 | 11545 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.Monad f => GHC.Internal.Base.Monad (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11554,11 +11554,11 @@ instance GHC.Internal.Base.MonadPlus [] -- Defined in ‘GHC.Internal.Base’ |
| 11554 | 11554 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
|
| 11555 | 11555 | instance forall (a :: * -> * -> *). (GHC.Internal.Control.Arrow.ArrowApply a, GHC.Internal.Control.Arrow.ArrowPlus a) => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11556 | 11556 | instance forall (m :: * -> *) a. GHC.Internal.Base.MonadPlus m => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11557 | -instance GHC.Internal.Base.MonadPlus GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11558 | 11557 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11559 | 11558 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11560 | 11559 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11561 | 11560 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11561 | +instance GHC.Internal.Base.MonadPlus GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11562 | 11562 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11563 | 11563 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| 11564 | 11564 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11578,7 +11578,6 @@ instance forall a b c d. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b |
| 11578 | 11578 | instance forall a b c d e. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d, GHC.Internal.Base.Monoid e) => GHC.Internal.Base.Monoid (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’
|
| 11579 | 11579 | instance GHC.Internal.Base.Monoid () -- Defined in ‘GHC.Internal.Base’
|
| 11580 | 11580 | instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11581 | -instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11582 | 11581 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11583 | 11582 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11584 | 11583 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11609,6 +11608,7 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I |
| 11609 | 11608 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11610 | 11609 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11611 | 11610 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11611 | +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11612 | 11612 | instance GHC.Internal.Base.Monoid GHC.Internal.Event.Windows.EventData -- Defined in ‘GHC.Internal.Event.Windows’
|
| 11613 | 11613 | instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Monoid (f p), GHC.Internal.Base.Monoid (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 11614 | 11614 | instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Monoid (f (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11631,7 +11631,6 @@ instance forall a b c d e. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Sem |
| 11631 | 11631 | instance GHC.Internal.Base.Semigroup () -- Defined in ‘GHC.Internal.Base’
|
| 11632 | 11632 | instance GHC.Internal.Base.Semigroup GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
|
| 11633 | 11633 | instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11634 | -instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11635 | 11634 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11636 | 11635 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11637 | 11636 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11669,6 +11668,7 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define |
| 11669 | 11668 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11670 | 11669 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11671 | 11670 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11671 | +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11672 | 11672 | instance GHC.Internal.Base.Semigroup GHC.Internal.Event.Windows.EventData -- Defined in ‘GHC.Internal.Event.Windows’
|
| 11673 | 11673 | instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Semigroup (f p), GHC.Internal.Base.Semigroup (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| 11674 | 11674 | instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Semigroup (f (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11768,7 +11768,6 @@ instance forall a. GHC.Internal.Classes.Eq a => GHC.Internal.Classes.Eq (GHC.Int |
| 11768 | 11768 | instance forall a. GHC.Internal.Classes.Eq (Control.Concurrent.Chan.Chan a) -- Defined in ‘Control.Concurrent.Chan’
|
| 11769 | 11769 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.MVar.MVar a) -- Defined in ‘GHC.Internal.MVar’
|
| 11770 | 11770 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.BlockReason -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11771 | -instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Conc.Sync.TVar a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11772 | 11771 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadId -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11773 | 11772 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadStatus -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11774 | 11773 | instance GHC.Internal.Classes.Eq GHC.Internal.IO.Exception.ArrayException -- Defined in ‘GHC.Internal.IO.Exception’
|
| ... | ... | @@ -11899,6 +11898,7 @@ instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Internal.Classes.Eq e) => GHC.In |
| 11899 | 11898 | instance forall s i e. GHC.Internal.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
|
| 11900 | 11899 | instance GHC.Internal.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
|
| 11901 | 11900 | instance GHC.Internal.Classes.Eq GHC.Internal.Event.Windows.ConsoleEvent.ConsoleEvent -- Defined in ‘GHC.Internal.Event.Windows.ConsoleEvent’
|
| 11901 | +instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.STM.TVar a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11902 | 11902 | instance GHC.Internal.Classes.Eq GHC.Internal.Event.TimeOut.TimeoutKey -- Defined in ‘GHC.Internal.Event.TimeOut’
|
| 11903 | 11903 | instance GHC.Internal.Classes.Eq GHC.Internal.Event.Windows.HandleKey -- Defined in ‘GHC.Internal.Event.Windows’
|
| 11904 | 11904 | instance GHC.Internal.Classes.Eq GHC.Internal.Event.Windows.FFI.IOCP -- Defined in ‘GHC.Internal.Event.Windows.FFI’
|
| ... | ... | @@ -146,9 +146,9 @@ module Control.Concurrent where |
| 146 | 146 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 147 | 147 | threadDelay :: GHC.Internal.Types.Int -> GHC.Internal.Types.IO ()
|
| 148 | 148 | threadWaitRead :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 149 | - threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 149 | + threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 150 | 150 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 151 | - threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.Conc.Sync.STM (), GHC.Internal.Types.IO ())
|
|
| 151 | + threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (GHC.Internal.STM.STM (), GHC.Internal.Types.IO ())
|
|
| 152 | 152 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 153 | 153 | tryPutMVar :: forall a. MVar a -> a -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| 154 | 154 | tryReadMVar :: forall a. MVar a -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe a)
|
| ... | ... | @@ -5117,7 +5117,7 @@ module GHC.Conc where |
| 5117 | 5117 | threadWaitReadSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5118 | 5118 | threadWaitWrite :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO ()
|
| 5119 | 5119 | threadWaitWriteSTM :: GHC.Internal.System.Posix.Types.Fd -> GHC.Internal.Types.IO (STM (), GHC.Internal.Types.IO ())
|
| 5120 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5120 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5121 | 5121 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5122 | 5122 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5123 | 5123 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -5197,7 +5197,7 @@ module GHC.Conc.Sync where |
| 5197 | 5197 | threadCapability :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Types.Int, GHC.Internal.Types.Bool)
|
| 5198 | 5198 | threadLabel :: ThreadId -> GHC.Internal.Types.IO (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
| 5199 | 5199 | threadStatus :: ThreadId -> GHC.Internal.Types.IO ThreadStatus
|
| 5200 | - throwSTM :: forall e a. GHC.Internal.Exception.Type.Exception e => e -> STM a
|
|
| 5200 | + throwSTM :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, GHC.Internal.Exception.Type.Exception e) => e -> STM a
|
|
| 5201 | 5201 | throwTo :: forall e. GHC.Internal.Exception.Type.Exception e => ThreadId -> e -> GHC.Internal.Types.IO ()
|
| 5202 | 5202 | unsafeIOToSTM :: forall a. GHC.Internal.Types.IO a -> STM a
|
| 5203 | 5203 | withMVar :: forall a b. GHC.Internal.MVar.MVar a -> (a -> GHC.Internal.Types.IO b) -> GHC.Internal.Types.IO b
|
| ... | ... | @@ -11117,12 +11117,12 @@ instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in |
| 11117 | 11117 | instance GHC.Internal.Base.Alternative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11118 | 11118 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowPlus a => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11119 | 11119 | instance forall (m :: * -> *) a. GHC.Internal.Base.Alternative m => GHC.Internal.Base.Alternative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11120 | -instance GHC.Internal.Base.Alternative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11121 | 11120 | instance GHC.Internal.Base.Alternative GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11122 | 11121 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
|
| 11123 | 11122 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11124 | 11123 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11125 | 11124 | instance forall (f :: * -> *). GHC.Internal.Base.Alternative f => GHC.Internal.Base.Alternative (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11125 | +instance GHC.Internal.Base.Alternative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11126 | 11126 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Alternative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11127 | 11127 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Alternative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Alternative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11128 | 11128 | instance forall (f :: * -> *). (GHC.Internal.Generics.Generic1 f, GHC.Internal.Base.Alternative (GHC.Internal.Generics.Rep1 f)) => GHC.Internal.Base.Alternative (GHC.Internal.Generics.Generically1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11146,7 +11146,6 @@ instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Applicative ( |
| 11146 | 11146 | instance GHC.Internal.Base.Applicative GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11147 | 11147 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11148 | 11148 | instance forall (m :: * -> *) a. GHC.Internal.Base.Applicative m => GHC.Internal.Base.Applicative (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11149 | -instance GHC.Internal.Base.Applicative GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11150 | 11149 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11151 | 11150 | instance forall s. GHC.Internal.Base.Applicative (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11152 | 11151 | instance GHC.Internal.Base.Applicative Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11168,6 +11167,7 @@ instance GHC.Internal.Base.Applicative Data.Semigroup.First -- Defined in ‘Dat |
| 11168 | 11167 | instance GHC.Internal.Base.Applicative Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11169 | 11168 | instance GHC.Internal.Base.Applicative Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11170 | 11169 | instance GHC.Internal.Base.Applicative Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11170 | +instance GHC.Internal.Base.Applicative GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11171 | 11171 | instance GHC.Internal.Base.Applicative GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11172 | 11172 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11173 | 11173 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Applicative f, GHC.Internal.Base.Applicative g) => GHC.Internal.Base.Applicative (f GHC.Internal.Generics.:.: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11197,7 +11197,6 @@ instance forall m. GHC.Internal.Base.Functor (GHC.Internal.Data.Functor.Const.Co |
| 11197 | 11197 | instance GHC.Internal.Base.Functor GHC.Internal.Functor.ZipList.ZipList -- Defined in ‘GHC.Internal.Functor.ZipList’
|
| 11198 | 11198 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.Arrow a => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11199 | 11199 | instance forall (m :: * -> *) a. GHC.Internal.Base.Functor m => GHC.Internal.Base.Functor (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11200 | -instance GHC.Internal.Base.Functor GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11201 | 11200 | instance GHC.Internal.Base.Functor GHC.Internal.Control.Exception.Handler -- Defined in ‘GHC.Internal.Control.Exception’
|
| 11202 | 11201 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11203 | 11202 | instance forall s. GHC.Internal.Base.Functor (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11223,6 +11222,7 @@ instance GHC.Internal.Base.Functor Data.Semigroup.Last -- Defined in ‘Data.Sem |
| 11223 | 11222 | instance GHC.Internal.Base.Functor Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11224 | 11223 | instance GHC.Internal.Base.Functor Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11225 | 11224 | instance forall i. GHC.Internal.Base.Functor (GHC.Internal.Arr.Array i) -- Defined in ‘GHC.Internal.Arr’
|
| 11225 | +instance GHC.Internal.Base.Functor GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11226 | 11226 | instance GHC.Internal.Base.Functor GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11227 | 11227 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11228 | 11228 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Functor f, GHC.Internal.Base.Functor g) => GHC.Internal.Base.Functor (f GHC.Internal.Generics.:+: g) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11257,7 +11257,6 @@ instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => |
| 11257 | 11257 | instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monad ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’
|
| 11258 | 11258 | instance forall (a :: * -> * -> *). GHC.Internal.Control.Arrow.ArrowApply a => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11259 | 11259 | instance forall (m :: * -> *) a. GHC.Internal.Base.Monad m => GHC.Internal.Base.Monad (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11260 | -instance GHC.Internal.Base.Monad GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11261 | 11260 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.ST.ST s) -- Defined in ‘GHC.Internal.ST’
|
| 11262 | 11261 | instance forall s. GHC.Internal.Base.Monad (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| 11263 | 11262 | instance GHC.Internal.Base.Monad Data.Complex.Complex -- Defined in ‘Data.Complex’
|
| ... | ... | @@ -11278,6 +11277,7 @@ instance GHC.Internal.Base.Monad Data.Semigroup.First -- Defined in ‘Data.Semi |
| 11278 | 11277 | instance GHC.Internal.Base.Monad Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
|
| 11279 | 11278 | instance GHC.Internal.Base.Monad Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
|
| 11280 | 11279 | instance GHC.Internal.Base.Monad Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
|
| 11280 | +instance GHC.Internal.Base.Monad GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11281 | 11281 | instance GHC.Internal.Base.Monad GHC.Internal.GHCi.NoIO -- Defined in ‘GHC.Internal.GHCi’
|
| 11282 | 11282 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.Monad f, GHC.Internal.Base.Monad g) => GHC.Internal.Base.Monad (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11283 | 11283 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.Monad f => GHC.Internal.Base.Monad (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11292,11 +11292,11 @@ instance GHC.Internal.Base.MonadPlus [] -- Defined in ‘GHC.Internal.Base’ |
| 11292 | 11292 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
|
| 11293 | 11293 | instance forall (a :: * -> * -> *). (GHC.Internal.Control.Arrow.ArrowApply a, GHC.Internal.Control.Arrow.ArrowPlus a) => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.ArrowMonad a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11294 | 11294 | instance forall (m :: * -> *) a. GHC.Internal.Base.MonadPlus m => GHC.Internal.Base.MonadPlus (GHC.Internal.Control.Arrow.Kleisli m a) -- Defined in ‘GHC.Internal.Control.Arrow’
|
| 11295 | -instance GHC.Internal.Base.MonadPlus GHC.Internal.Conc.Sync.STM -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11296 | 11295 | instance GHC.Internal.Base.MonadPlus GHC.Internal.Data.Proxy.Proxy -- Defined in ‘GHC.Internal.Data.Proxy’
|
| 11297 | 11296 | instance [safe] forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (Data.Functor.Product.Product f g) -- Defined in ‘Data.Functor.Product’
|
| 11298 | 11297 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Semigroup.Internal.Alt f) -- Defined in ‘GHC.Internal.Data.Semigroup.Internal’
|
| 11299 | 11298 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Data.Monoid.Ap f) -- Defined in ‘GHC.Internal.Data.Monoid’
|
| 11299 | +instance GHC.Internal.Base.MonadPlus GHC.Internal.STM.STM -- Defined in ‘GHC.Internal.STM’
|
|
| 11300 | 11300 | instance forall (f :: * -> *) (g :: * -> *). (GHC.Internal.Base.MonadPlus f, GHC.Internal.Base.MonadPlus g) => GHC.Internal.Base.MonadPlus (f GHC.Internal.Generics.:*: g) -- Defined in ‘GHC.Internal.Generics’
|
| 11301 | 11301 | instance forall (f :: * -> *) i (c :: GHC.Internal.Generics.Meta). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.M1 i c f) -- Defined in ‘GHC.Internal.Generics’
|
| 11302 | 11302 | instance forall (f :: * -> *). GHC.Internal.Base.MonadPlus f => GHC.Internal.Base.MonadPlus (GHC.Internal.Generics.Rec1 f) -- Defined in ‘GHC.Internal.Generics’
|
| ... | ... | @@ -11316,7 +11316,6 @@ instance forall a b c d. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b |
| 11316 | 11316 | instance forall a b c d e. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d, GHC.Internal.Base.Monoid e) => GHC.Internal.Base.Monoid (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’
|
| 11317 | 11317 | instance GHC.Internal.Base.Monoid () -- Defined in ‘GHC.Internal.Base’
|
| 11318 | 11318 | instance forall a k (b :: k). GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11319 | -instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11320 | 11319 | instance GHC.Internal.Base.Monoid GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11321 | 11320 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11322 | 11321 | instance forall a s. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11347,6 +11346,7 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I |
| 11347 | 11346 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11348 | 11347 | instance forall a. (GHC.Internal.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11349 | 11348 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11349 | +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11350 | 11350 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11351 | 11351 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11352 | 11352 | instance GHC.Internal.Base.Monoid ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| ... | ... | @@ -11371,7 +11371,6 @@ instance forall a b c d e. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Sem |
| 11371 | 11371 | instance GHC.Internal.Base.Semigroup () -- Defined in ‘GHC.Internal.Base’
|
| 11372 | 11372 | instance GHC.Internal.Base.Semigroup GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
|
| 11373 | 11373 | instance forall a k (b :: k). GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
|
| 11374 | -instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Conc.Sync.STM a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11375 | 11374 | instance GHC.Internal.Base.Semigroup GHC.Internal.Exception.Context.ExceptionContext -- Defined in ‘GHC.Internal.Exception.Context’
|
| 11376 | 11375 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.ST.ST s a) -- Defined in ‘GHC.Internal.ST’
|
| 11377 | 11376 | instance forall a s. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a) -- Defined in ‘GHC.Internal.Control.Monad.ST.Lazy.Imp’
|
| ... | ... | @@ -11409,6 +11408,7 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define |
| 11409 | 11408 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
|
| 11410 | 11409 | instance forall a. GHC.Internal.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
|
| 11411 | 11410 | instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
|
| 11411 | +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.STM.STM a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11412 | 11412 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11413 | 11413 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11414 | 11414 | instance GHC.Internal.Base.Semigroup ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| ... | ... | @@ -11510,7 +11510,6 @@ instance forall a. GHC.Internal.Classes.Eq a => GHC.Internal.Classes.Eq (GHC.Int |
| 11510 | 11510 | instance forall a. GHC.Internal.Classes.Eq (Control.Concurrent.Chan.Chan a) -- Defined in ‘Control.Concurrent.Chan’
|
| 11511 | 11511 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.MVar.MVar a) -- Defined in ‘GHC.Internal.MVar’
|
| 11512 | 11512 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.BlockReason -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11513 | -instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Conc.Sync.TVar a) -- Defined in ‘GHC.Internal.Conc.Sync’
|
|
| 11514 | 11513 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadId -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11515 | 11514 | instance GHC.Internal.Classes.Eq GHC.Internal.Conc.Sync.ThreadStatus -- Defined in ‘GHC.Internal.Conc.Sync’
|
| 11516 | 11515 | instance GHC.Internal.Classes.Eq GHC.Internal.IO.Exception.ArrayException -- Defined in ‘GHC.Internal.IO.Exception’
|
| ... | ... | @@ -11640,6 +11639,7 @@ instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.Foreign.C.ConstPtr.Cons |
| 11640 | 11639 | instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Internal.Classes.Eq e) => GHC.Internal.Classes.Eq (GHC.Internal.Arr.Array i e) -- Defined in ‘GHC.Internal.Arr’
|
| 11641 | 11640 | instance forall s i e. GHC.Internal.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
|
| 11642 | 11641 | instance GHC.Internal.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
|
| 11642 | +instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.STM.TVar a) -- Defined in ‘GHC.Internal.STM’
|
|
| 11643 | 11643 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11644 | 11644 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|
| 11645 | 11645 | instance GHC.Internal.Classes.Eq ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1500.0:GHC.Internal.Event.Internal.Types’
|