{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module NoThunks.Class (
NoThunks(..)
, ThunkInfo(..)
, Context
, Info
, unsafeNoThunks
, allNoThunks
, noThunksInValues
, noThunksInKeysAndValues
, OnlyCheckWhnf(..)
, OnlyCheckWhnfNamed(..)
, InspectHeap(..)
, InspectHeapNamed(..)
, AllowThunk(..)
, AllowThunksIn(..)
, GWNoThunks(..)
) where
import Data.Proxy
import Data.Typeable
import System.IO.Unsafe (unsafePerformIO)
import GHC.Exts.Heap
import GHC.Generics
import GHC.Records
import GHC.TypeLits
import GHC.Conc.Sync (ThreadId (..))
import Data.Foldable (toList)
import Data.Functor.Identity (Identity)
import Data.Int
import Data.IntMap (IntMap)
import Data.Kind (Type)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Map (Map)
import Data.Ratio
import Data.Sequence (Seq)
import Data.Set (Set)
import Data.Time
#if MIN_VERSION_base(4,16,0)
import Data.Tuple (Solo (..))
#endif
import Data.Void (Void)
import Data.Word
import GHC.Stack
#if !MIN_VERSION_base(4,16,0)
import Numeric.Natural
#endif
#if MIN_VERSION_base(4,16,0)
import GHC.InfoProv.Compat
#endif
import qualified Control.Concurrent.MVar as MVar
import qualified Control.Concurrent.STM.TVar as TVar
import qualified Data.IntMap as IntMap
import qualified Data.IORef as IORef
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Monoid as Monoid
import qualified Data.Semigroup as Semigroup
#ifdef MIN_VERSION_bytestring
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString as BS.Strict
import qualified Data.ByteString.Lazy as BS.Lazy
import qualified Data.ByteString.Lazy.Internal as BS.Lazy.Internal
#endif
#ifdef MIN_VERSION_text
import qualified Data.Text as Text.Strict
import qualified Data.Text.Internal.Lazy as Text.Lazy.Internal
import qualified Data.Text.Lazy as Text.Lazy
#endif
#ifdef MIN_VERSION_vector
import qualified Data.Vector as Vector.Boxed
import qualified Data.Vector.Unboxed as Vector.Unboxed
#endif
class NoThunks a where
noThunks :: Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt a
x = do
Bool
isThunk <- a -> IO Bool
forall a. a -> IO Bool
checkIsThunk a
x
let ctxt' :: Context
ctxt' = Proxy a -> String
forall a. NoThunks a => Proxy a -> String
showTypeOf (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) String -> Context -> Context
forall a. a -> [a] -> [a]
: Context
ctxt
ThunkInfo
thunkInfo <- Context -> a -> IO ThunkInfo
forall a. Context -> a -> IO ThunkInfo
getThunkInfo Context
ctxt' a
x
if Bool
isThunk
then Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ThunkInfo -> IO (Maybe ThunkInfo))
-> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a b. (a -> b) -> a -> b
$ ThunkInfo -> Maybe ThunkInfo
forall a. a -> Maybe a
Just ThunkInfo
thunkInfo
else Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt' a
x
wNoThunks :: Context -> a -> IO (Maybe ThunkInfo)
default wNoThunks :: (Generic a, GWNoThunks '[] (Rep a))
=> Context -> a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt a
x = Proxy '[] -> Context -> Rep a Any -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy '[] -> Context -> Rep a x -> IO (Maybe ThunkInfo)
gwNoThunks (forall (t :: [Symbol]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @'[]) Context
ctxt Rep a Any
forall x. Rep a x
fp
where
fp :: Rep a x
!fp :: forall x. Rep a x
fp = a -> Rep a x
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from a
x
showTypeOf :: Proxy a -> String
default showTypeOf :: (Generic a, GShowTypeOf (Rep a)) => Proxy a -> String
showTypeOf Proxy a
_ = Rep a Any -> String
forall x. Rep a x -> String
forall (f :: * -> *) x. GShowTypeOf f => f x -> String
gShowTypeOf (a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from a
x)
where
x :: a
x :: a
x = a
x
type Context = [String]
type Info = String
newtype ThunkInfo = ThunkInfo { ThunkInfo -> Either Context String
thunkInfo :: Either Context Info }
deriving Int -> ThunkInfo -> ShowS
[ThunkInfo] -> ShowS
ThunkInfo -> String
(Int -> ThunkInfo -> ShowS)
-> (ThunkInfo -> String)
-> ([ThunkInfo] -> ShowS)
-> Show ThunkInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThunkInfo -> ShowS
showsPrec :: Int -> ThunkInfo -> ShowS
$cshow :: ThunkInfo -> String
show :: ThunkInfo -> String
$cshowList :: [ThunkInfo] -> ShowS
showList :: [ThunkInfo] -> ShowS
Show
getThunkInfo :: Context -> a -> IO ThunkInfo
#if MIN_VERSION_base(4,16,0)
getThunkInfo :: forall a. Context -> a -> IO ThunkInfo
getThunkInfo Context
ctxt a
a = Either Context String -> ThunkInfo
ThunkInfo (Either Context String -> ThunkInfo)
-> (Maybe InfoProv -> Either Context String)
-> Maybe InfoProv
-> ThunkInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Context String
-> (InfoProv -> Either Context String)
-> Maybe InfoProv
-> Either Context String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Context -> Either Context String
forall a b. a -> Either a b
Left Context
ctxt) (String -> Either Context String
forall a b. b -> Either a b
Right (String -> Either Context String)
-> (InfoProv -> String) -> InfoProv -> Either Context String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InfoProv -> String
fmt) (Maybe InfoProv -> ThunkInfo)
-> IO (Maybe InfoProv) -> IO ThunkInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> IO (Maybe InfoProv)
forall a. a -> IO (Maybe InfoProv)
whereFrom a
a
where
fmt :: InfoProv -> Info
fmt :: InfoProv -> String
fmt InfoProv { String
ipSrcFile :: String
ipSrcFile :: InfoProv -> String
ipSrcFile, String
ipSrcSpan :: String
ipSrcSpan :: InfoProv -> String
ipSrcSpan,
String
ipLabel :: String
ipLabel :: InfoProv -> String
ipLabel, String
ipTyDesc :: String
ipTyDesc :: InfoProv -> String
ipTyDesc } =
String
ipLabel String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ipTyDesc
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" @ " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ipSrcFile String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ipSrcSpan
#else
getThunkInfo ctxt _ = return (ThunkInfo (Left ctxt))
#endif
{-# NOINLINE unsafeNoThunks #-}
unsafeNoThunks :: NoThunks a => a -> Maybe ThunkInfo
unsafeNoThunks :: forall a. NoThunks a => a -> Maybe ThunkInfo
unsafeNoThunks a
a = IO (Maybe ThunkInfo) -> Maybe ThunkInfo
forall a. IO a -> a
unsafePerformIO (IO (Maybe ThunkInfo) -> Maybe ThunkInfo)
-> IO (Maybe ThunkInfo) -> Maybe ThunkInfo
forall a b. (a -> b) -> a -> b
$ Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks [] a
a
allNoThunks :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks = [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
go
where
go :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
go :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
go [] = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
go (IO (Maybe ThunkInfo)
a:[IO (Maybe ThunkInfo)]
as) = do
Maybe ThunkInfo
nf <- IO (Maybe ThunkInfo)
a
case Maybe ThunkInfo
nf of
Maybe ThunkInfo
Nothing -> [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
go [IO (Maybe ThunkInfo)]
as
Just ThunkInfo
thunk -> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ThunkInfo -> IO (Maybe ThunkInfo))
-> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a b. (a -> b) -> a -> b
$ ThunkInfo -> Maybe ThunkInfo
forall a. a -> Maybe a
Just ThunkInfo
thunk
noThunksInValues :: NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues :: forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt = [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks ([IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo))
-> ([a] -> [IO (Maybe ThunkInfo)]) -> [a] -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> IO (Maybe ThunkInfo)) -> [a] -> [IO (Maybe ThunkInfo)]
forall a b. (a -> b) -> [a] -> [b]
map (Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt)
noThunksInKeysAndValues :: (NoThunks k, NoThunks v)
=> Context -> [(k, v)] -> IO (Maybe ThunkInfo)
noThunksInKeysAndValues :: forall k v.
(NoThunks k, NoThunks v) =>
Context -> [(k, v)] -> IO (Maybe ThunkInfo)
noThunksInKeysAndValues Context
ctxt =
[IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks
([IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo))
-> ([(k, v)] -> [IO (Maybe ThunkInfo)])
-> [(k, v)]
-> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((k, v) -> [IO (Maybe ThunkInfo)])
-> [(k, v)] -> [IO (Maybe ThunkInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(k
k, v
v) -> [ Context -> k -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt k
k
, Context -> v -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt v
v
])
newtype OnlyCheckWhnf a = OnlyCheckWhnf a
newtype OnlyCheckWhnfNamed (name :: Symbol) a = OnlyCheckWhnfNamed a
newtype AllowThunk a = AllowThunk a
newtype AllowThunksIn (fields :: [Symbol]) a = AllowThunksIn a
newtype InspectHeap a = InspectHeap a
newtype InspectHeapNamed (name :: Symbol) a = InspectHeapNamed a
instance Typeable a => NoThunks (OnlyCheckWhnf a) where
showTypeOf :: Proxy (OnlyCheckWhnf a) -> String
showTypeOf Proxy (OnlyCheckWhnf a)
_ = TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
wNoThunks :: Context -> OnlyCheckWhnf a -> IO (Maybe ThunkInfo)
wNoThunks Context
_ OnlyCheckWhnf a
_ = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
instance KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) where
showTypeOf :: Proxy (OnlyCheckWhnfNamed name a) -> String
showTypeOf Proxy (OnlyCheckWhnfNamed name a)
_ = Proxy name -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @name)
wNoThunks :: Context -> OnlyCheckWhnfNamed name a -> IO (Maybe ThunkInfo)
wNoThunks Context
_ OnlyCheckWhnfNamed name a
_ = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
instance NoThunks (AllowThunk a) where
showTypeOf :: Proxy (AllowThunk a) -> String
showTypeOf Proxy (AllowThunk a)
_ = String
"<never used since never fails>"
noThunks :: Context -> AllowThunk a -> IO (Maybe ThunkInfo)
noThunks Context
_ AllowThunk a
_ = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
wNoThunks :: Context -> AllowThunk a -> IO (Maybe ThunkInfo)
wNoThunks = Context -> AllowThunk a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks
instance (HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a))
=> NoThunks (AllowThunksIn s a) where
showTypeOf :: Proxy (AllowThunksIn s a) -> String
showTypeOf Proxy (AllowThunksIn s a)
_ = TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
wNoThunks :: Context -> AllowThunksIn s a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt (AllowThunksIn a
x) = Proxy s -> Context -> Rep a Any -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy s -> Context -> Rep a x -> IO (Maybe ThunkInfo)
gwNoThunks (forall (t :: [Symbol]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @s) Context
ctxt Rep a Any
forall x. Rep a x
fp
where
fp :: Rep a x
!fp :: forall x. Rep a x
fp = a -> Rep a x
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from a
x
instance Typeable a => NoThunks (InspectHeap a) where
showTypeOf :: Proxy (InspectHeap a) -> String
showTypeOf Proxy (InspectHeap a)
_ = TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a)
wNoThunks :: Context -> InspectHeap a -> IO (Maybe ThunkInfo)
wNoThunks = Context -> InspectHeap a -> IO (Maybe ThunkInfo)
forall a. Context -> a -> IO (Maybe ThunkInfo)
inspectHeap
instance KnownSymbol name => NoThunks (InspectHeapNamed name a) where
showTypeOf :: Proxy (InspectHeapNamed name a) -> String
showTypeOf Proxy (InspectHeapNamed name a)
_ = Proxy name -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @name)
wNoThunks :: Context -> InspectHeapNamed name a -> IO (Maybe ThunkInfo)
wNoThunks = Context -> InspectHeapNamed name a -> IO (Maybe ThunkInfo)
forall a. Context -> a -> IO (Maybe ThunkInfo)
inspectHeap
inspectHeap :: Context -> a -> IO (Maybe ThunkInfo)
inspectHeap :: forall a. Context -> a -> IO (Maybe ThunkInfo)
inspectHeap Context
ctxt a
x = do
Bool
containsThunks <- a -> IO Bool
forall a. a -> IO Bool
checkContainsThunks a
x
ThunkInfo
thunkInfo <- Context -> a -> IO ThunkInfo
forall a. Context -> a -> IO ThunkInfo
getThunkInfo (String
"..." String -> Context -> Context
forall a. a -> [a] -> [a]
: Context
ctxt) a
x
Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ThunkInfo -> IO (Maybe ThunkInfo))
-> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a b. (a -> b) -> a -> b
$ if Bool
containsThunks
then ThunkInfo -> Maybe ThunkInfo
forall a. a -> Maybe a
Just ThunkInfo
thunkInfo
else Maybe ThunkInfo
forall a. Maybe a
Nothing
class GWNoThunks (a :: [Symbol]) f where
gwNoThunks :: proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
instance GWNoThunks a f => GWNoThunks a (D1 c f) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> D1 c f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt (M1 f x
fp) = proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt f x
fp
instance GWNoThunks a f => GWNoThunks a (C1 c f) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> C1 c f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt (M1 f x
fp) = proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt f x
fp
instance GWNoThunks a f => GWNoThunks a (S1 ('MetaSel 'Nothing su ss ds) f) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a
-> Context
-> S1 ('MetaSel 'Nothing su ss ds) f x
-> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt (M1 f x
fp) = proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt f x
fp
instance (GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :*: g) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> (:*:) f g x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt (f x
fp :*: g x
gp) = [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks [
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt f x
fp
, proxy a -> Context -> g x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> g x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt g x
gp
]
instance (GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :+: g) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> (:+:) f g x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt (L1 f x
fp) = proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt f x
fp
gwNoThunks proxy a
a Context
ctxt (R1 g x
gp) = proxy a -> Context -> g x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> g x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
a Context
ctxt g x
gp
instance NoThunks c => GWNoThunks a (K1 i c) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> K1 i c x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
_a Context
ctxt (K1 c
c) = Context -> c -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt' c
c
where
ctxt' :: Context
ctxt' = case Context
ctxt of
String
hd : Context
tl | String
hd String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy c -> String
forall a. NoThunks a => Proxy a -> String
showTypeOf (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c) -> Context
tl
Context
_otherwise -> Context
ctxt
instance GWNoThunks a U1 where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> U1 x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
_a Context
_ctxt U1 x
U1 = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
instance GWNoThunks a V1 where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a -> Context -> V1 x -> IO (Maybe ThunkInfo)
gwNoThunks proxy a
_a Context
_ctxt V1 x
_ = String -> IO (Maybe ThunkInfo)
forall a. HasCallStack => String -> a
error String
"unreachable gwNoThunks @V1"
instance ( GWRecordField f (Elem fieldName a)
, KnownSymbol fieldName
)
=> GWNoThunks a (S1 ('MetaSel ('Just fieldName) su ss ds) f) where
gwNoThunks :: forall (proxy :: [Symbol] -> *) x.
proxy a
-> Context
-> S1 ('MetaSel ('Just fieldName) su ss ds) f x
-> IO (Maybe ThunkInfo)
gwNoThunks proxy a
_ Context
ctxt (M1 f x
fp) =
Proxy (Elem fieldName a) -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: Bool -> *) x.
proxy (Elem fieldName a) -> Context -> f x -> IO (Maybe ThunkInfo)
forall (f :: * -> *) (b :: Bool) (proxy :: Bool -> *) x.
GWRecordField f b =>
proxy b -> Context -> f x -> IO (Maybe ThunkInfo)
gwRecordField (forall (t :: Bool). Proxy t
forall {k} (t :: k). Proxy t
Proxy @(Elem fieldName a)) (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal @fieldName Proxy fieldName
forall {k} (t :: k). Proxy t
Proxy String -> Context -> Context
forall a. a -> [a] -> [a]
: Context
ctxt) f x
fp
class GWRecordField f (b :: Bool) where
gwRecordField :: proxy b -> Context -> f x -> IO (Maybe ThunkInfo)
instance GWRecordField f 'True where
gwRecordField :: forall (proxy :: Bool -> *) x.
proxy 'True -> Context -> f x -> IO (Maybe ThunkInfo)
gwRecordField proxy 'True
_ Context
_ f x
_ = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
instance GWNoThunks '[] f => GWRecordField f 'False where
gwRecordField :: forall (proxy :: Bool -> *) x.
proxy 'False -> Context -> f x -> IO (Maybe ThunkInfo)
gwRecordField proxy 'False
_ Context
ctxt f x
f = Proxy '[] -> Context -> f x -> IO (Maybe ThunkInfo)
forall (a :: [Symbol]) (f :: * -> *) (proxy :: [Symbol] -> *) x.
GWNoThunks a f =>
proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
forall (proxy :: [Symbol] -> *) x.
proxy '[] -> Context -> f x -> IO (Maybe ThunkInfo)
gwNoThunks (forall (t :: [Symbol]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @'[]) Context
ctxt f x
f
class GShowTypeOf f where
gShowTypeOf :: f x -> String
instance Datatype c => GShowTypeOf (D1 c f) where
gShowTypeOf :: forall x. D1 c f x -> String
gShowTypeOf = M1 D c f x -> String
forall {k} (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> String
forall k1 (t :: Meta -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t c f a -> String
datatypeName
deriving via OnlyCheckWhnf Bool instance NoThunks Bool
deriving via OnlyCheckWhnf Natural instance NoThunks Natural
deriving via OnlyCheckWhnf Integer instance NoThunks Integer
deriving via OnlyCheckWhnf Float instance NoThunks Float
deriving via OnlyCheckWhnf Double instance NoThunks Double
deriving via OnlyCheckWhnf Char instance NoThunks Char
deriving via OnlyCheckWhnf Int instance NoThunks Int
deriving via OnlyCheckWhnf Int8 instance NoThunks Int8
deriving via OnlyCheckWhnf Int16 instance NoThunks Int16
deriving via OnlyCheckWhnf Int32 instance NoThunks Int32
deriving via OnlyCheckWhnf Int64 instance NoThunks Int64
deriving via OnlyCheckWhnf Word instance NoThunks Word
deriving via OnlyCheckWhnf Word8 instance NoThunks Word8
deriving via OnlyCheckWhnf Word16 instance NoThunks Word16
deriving via OnlyCheckWhnf Word32 instance NoThunks Word32
deriving via OnlyCheckWhnf Word64 instance NoThunks Word64
deriving via a instance NoThunks a => NoThunks (Semigroup.Min a)
deriving via a instance NoThunks a => NoThunks (Semigroup.Max a)
deriving via a instance NoThunks a => NoThunks (Semigroup.First a)
deriving via a instance NoThunks a => NoThunks (Semigroup.Last a)
deriving via a instance NoThunks a => NoThunks (Semigroup.Dual a)
deriving via Bool instance NoThunks Semigroup.All
deriving via Bool instance NoThunks Semigroup.Any
deriving via a instance NoThunks a => NoThunks (Semigroup.Sum a)
deriving via a instance NoThunks a => NoThunks (Semigroup.Product a)
deriving via a instance NoThunks a => NoThunks (Semigroup.WrappedMonoid a)
instance (NoThunks a, NoThunks b) => NoThunks (Semigroup.Arg a b)
deriving via (Maybe a) instance NoThunks a => NoThunks (Monoid.First a)
deriving via (Maybe a) instance NoThunks a => NoThunks (Monoid.Last a)
deriving via (f a) instance NoThunks (f a) => NoThunks (Monoid.Alt f a)
deriving via (f a) instance NoThunks (f a) => NoThunks (Monoid.Ap f a)
#if MIN_VERSION_base(4,18,0)
instance NoThunks a => NoThunks (Solo a) where
wNoThunks :: Context -> Solo a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctx (MkSolo a
a) = Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
wNoThunks (String
"Solo" String -> Context -> Context
forall a. a -> [a] -> [a]
: Context
ctx) a
a
#elif MIN_VERSION_base(4,16,0)
instance NoThunks a => NoThunks (Solo a) where
wNoThunks ctx (Solo a) = wNoThunks ("Solo" : ctx) a
#endif
instance NoThunks a => NoThunks (IORef.IORef a) where
showTypeOf :: Proxy (IORef a) -> String
showTypeOf Proxy (IORef a)
_ = String
"IORef"
wNoThunks :: Context -> IORef a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctx IORef a
ref = do
a
val <- IORef a -> IO a
forall a. IORef a -> IO a
IORef.readIORef IORef a
ref
Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctx a
val
instance NoThunks a => NoThunks (MVar.MVar a) where
showTypeOf :: Proxy (MVar a) -> String
showTypeOf Proxy (MVar a)
_ = String
"MVar"
wNoThunks :: Context -> MVar a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctx MVar a
ref = do
Maybe a
val <- MVar a -> IO (Maybe a)
forall a. MVar a -> IO (Maybe a)
MVar.tryReadMVar MVar a
ref
IO (Maybe ThunkInfo)
-> (a -> IO (Maybe ThunkInfo)) -> Maybe a -> IO (Maybe ThunkInfo)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing) (Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctx) Maybe a
val
instance NoThunks a => NoThunks (TVar.TVar a) where
showTypeOf :: Proxy (TVar a) -> String
showTypeOf Proxy (TVar a)
_ = String
"TVar"
wNoThunks :: Context -> TVar a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctx TVar a
ref = do
a
val <- TVar a -> IO a
forall a. TVar a -> IO a
TVar.readTVarIO TVar a
ref
Context -> a -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctx a
val
deriving via InspectHeap Day instance NoThunks Day
deriving via InspectHeap DiffTime instance NoThunks DiffTime
deriving via InspectHeap LocalTime instance NoThunks LocalTime
deriving via InspectHeap NominalDiffTime instance NoThunks NominalDiffTime
deriving via InspectHeap TimeLocale instance NoThunks TimeLocale
deriving via InspectHeap TimeOfDay instance NoThunks TimeOfDay
deriving via InspectHeap TimeZone instance NoThunks TimeZone
deriving via InspectHeap UniversalTime instance NoThunks UniversalTime
deriving via InspectHeap UTCTime instance NoThunks UTCTime
deriving via InspectHeap ZonedTime instance NoThunks ZonedTime
#ifdef MIN_VERSION_bytestring
deriving via OnlyCheckWhnfNamed "Strict.ByteString" BS.Strict.ByteString
instance NoThunks BS.Strict.ByteString
deriving via OnlyCheckWhnfNamed "ShortByteString" ShortByteString
instance NoThunks ShortByteString
instance NoThunks BS.Lazy.ByteString where
showTypeOf :: Proxy ByteString -> String
showTypeOf Proxy ByteString
_ = String
"Lazy.ByteString"
wNoThunks :: Context -> ByteString -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt ByteString
bs =
case ByteString
bs of
ByteString
BS.Lazy.Internal.Empty -> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
BS.Lazy.Internal.Chunk ByteString
chunk ByteString
bs' -> [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks [
Context -> ByteString -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt ByteString
chunk
, Context -> ByteString -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt ByteString
bs'
]
#endif
#ifdef MIN_VERSION_text
deriving via OnlyCheckWhnfNamed "Strict.Text" Text.Strict.Text
instance NoThunks Text.Strict.Text
instance NoThunks Text.Lazy.Text where
showTypeOf :: Proxy Text -> String
showTypeOf Proxy Text
_ = String
"Lazy.Text"
wNoThunks :: Context -> Text -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt Text
bs =
case Text
bs of
Text
Text.Lazy.Internal.Empty -> Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
Text.Lazy.Internal.Chunk Text
chunk Text
bs' -> [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks [
Context -> Text -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Text
chunk
, Context -> Text -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Text
bs'
]
#endif
instance ( NoThunks a
, NoThunks b
) => NoThunks (a, b)
instance ( NoThunks a
, NoThunks b
, NoThunks c
) => NoThunks (a, b, c)
instance ( NoThunks a
, NoThunks b
, NoThunks c
, NoThunks d
) => NoThunks (a, b, c, d)
instance ( NoThunks a
, NoThunks b
, NoThunks c
, NoThunks d
, NoThunks e
) => NoThunks (a, b, c, d, e)
instance ( NoThunks a
, NoThunks b
, NoThunks c
, NoThunks d
, NoThunks e
, NoThunks f
) => NoThunks (a, b, c, d, e, f)
instance ( NoThunks a
, NoThunks b
, NoThunks c
, NoThunks d
, NoThunks e
, NoThunks f
, NoThunks g
) => NoThunks (a, b, c, d, e, f, g)
instance NoThunks Void
instance NoThunks ()
instance NoThunks a => NoThunks [a]
instance NoThunks a => NoThunks (Identity a)
instance NoThunks a => NoThunks (Maybe a)
instance NoThunks a => NoThunks (NonEmpty a)
instance (NoThunks a, NoThunks b) => NoThunks (Either a b)
deriving via InspectHeap ThreadId instance NoThunks ThreadId
instance (NoThunks k, NoThunks v) => NoThunks (Map k v) where
showTypeOf :: Proxy (Map k v) -> String
showTypeOf Proxy (Map k v)
_ = String
"Map"
wNoThunks :: Context -> Map k v -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt = Context -> [(k, v)] -> IO (Maybe ThunkInfo)
forall k v.
(NoThunks k, NoThunks v) =>
Context -> [(k, v)] -> IO (Maybe ThunkInfo)
noThunksInKeysAndValues Context
ctxt ([(k, v)] -> IO (Maybe ThunkInfo))
-> (Map k v -> [(k, v)]) -> Map k v -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map k v -> [(k, v)]
forall k a. Map k a -> [(k, a)]
Map.toList
instance NoThunks a => NoThunks (Set a) where
showTypeOf :: Proxy (Set a) -> String
showTypeOf Proxy (Set a)
_ = String
"Set"
wNoThunks :: Context -> Set a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt = Context -> [a] -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt ([a] -> IO (Maybe ThunkInfo))
-> (Set a -> [a]) -> Set a -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> [a]
forall a. Set a -> [a]
Set.toList
instance NoThunks a => NoThunks (IntMap a) where
showTypeOf :: Proxy (IntMap a) -> String
showTypeOf Proxy (IntMap a)
_ = String
"IntMap"
wNoThunks :: Context -> IntMap a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt = Context -> [(Int, a)] -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt ([(Int, a)] -> IO (Maybe ThunkInfo))
-> (IntMap a -> [(Int, a)]) -> IntMap a -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
IntMap.toList
#ifdef MIN_VERSION_vector
instance NoThunks a => NoThunks (Vector.Boxed.Vector a) where
showTypeOf :: Proxy (Vector a) -> String
showTypeOf Proxy (Vector a)
_ = String
"Boxed.Vector"
wNoThunks :: Context -> Vector a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt = Context -> [a] -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt ([a] -> IO (Maybe ThunkInfo))
-> (Vector a -> [a]) -> Vector a -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> [a]
forall a. Vector a -> [a]
Vector.Boxed.toList
instance NoThunks (Vector.Unboxed.Vector a) where
showTypeOf :: Proxy (Vector a) -> String
showTypeOf Proxy (Vector a)
_ = String
"Unboxed.Vector"
wNoThunks :: Context -> Vector a -> IO (Maybe ThunkInfo)
wNoThunks Context
_ Vector a
_ = Maybe ThunkInfo -> IO (Maybe ThunkInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThunkInfo
forall a. Maybe a
Nothing
#endif
deriving via OnlyCheckWhnfNamed "->" (a -> b) instance NoThunks (a -> b)
deriving via OnlyCheckWhnfNamed "IO" (IO a) instance NoThunks (IO a)
deriving via AllowThunk CallStack instance NoThunks CallStack
instance NoThunks a => NoThunks (Seq a) where
showTypeOf :: Proxy (Seq a) -> String
showTypeOf Proxy (Seq a)
_ = String
"Seq"
wNoThunks :: Context -> Seq a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt = Context -> [a] -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt ([a] -> IO (Maybe ThunkInfo))
-> (Seq a -> [a]) -> Seq a -> IO (Maybe ThunkInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq a -> [a]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
instance NoThunks a => NoThunks (Ratio a) where
showTypeOf :: Proxy (Ratio a) -> String
showTypeOf Proxy (Ratio a)
_ = String
"Ratio"
wNoThunks :: Context -> Ratio a -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt Ratio a
r = Context -> [a] -> IO (Maybe ThunkInfo)
forall a. NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
noThunksInValues Context
ctxt [a
n, a
d]
where
!n :: a
n = Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
r
!d :: a
d = Ratio a -> a
forall a. Ratio a -> a
denominator Ratio a
r
type family Same s t where
Same s t = IsSame (CmpSymbol s t)
type family IsSame (o :: Ordering) where
IsSame 'EQ = 'True
IsSame _x = 'False
type family Or (a :: Bool) (b :: Bool) where
Or 'False 'False = 'False
Or _a _b = 'True
type family Elem (s :: Symbol) (xs :: [Symbol]) where
Elem s (x ': xs) = Or (Same s x) (Elem s xs)
Elem _s '[] = 'False
class HasFields (s :: [Symbol]) (a :: Type)
instance HasFields '[] a
instance (HasField x a t, HasFields xs a) => HasFields (x ': xs) a
checkIsThunk :: a -> IO Bool
checkIsThunk :: forall a. a -> IO Bool
checkIsThunk a
x = Closure -> Bool
closureIsThunk (Closure -> Bool) -> IO Closure -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Box -> IO Closure
getBoxedClosureData (a -> Box
forall a. a -> Box
asBox a
x)
checkContainsThunks :: a -> IO Bool
checkContainsThunks :: forall a. a -> IO Bool
checkContainsThunks a
x = Box -> IO Bool
go (a -> Box
forall a. a -> Box
asBox a
x)
where
go :: Box -> IO Bool
go :: Box -> IO Bool
go Box
b = do
Closure
c <- Box -> IO Closure
getBoxedClosureData Box
b
if Closure -> Bool
closureIsThunk Closure
c then
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else do
Closure
c' <- Box -> IO Closure
getBoxedClosureData Box
b
(Box -> IO Bool) -> [Box] -> IO Bool
forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
anyM Box -> IO Bool
go (Closure -> [Box]
forall b. GenClosure b -> [b]
allClosures Closure
c')
closureIsThunk :: Closure -> Bool
closureIsThunk :: Closure -> Bool
closureIsThunk ThunkClosure{} = Bool
True
closureIsThunk APClosure{} = Bool
True
closureIsThunk SelectorClosure{} = Bool
True
closureIsThunk BCOClosure{} = Bool
True
closureIsThunk Closure
_ = Bool
False
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
anyM :: forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
anyM a -> m Bool
_ [] = Bool -> m Bool
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
anyM a -> m Bool
p (a
x : [a]
xs) = do
Bool
q <- a -> m Bool
p a
x
if Bool
q then Bool -> m Bool
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else (a -> m Bool) -> [a] -> m Bool
forall (m :: * -> *) a. Monad m => (a -> m Bool) -> [a] -> m Bool
anyM a -> m Bool
p [a]
xs