{-# LANGUAGE Rank2Types, MagicHash, UnboxedTuples, ExistentialQuantification #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-} -- SPEC2

-- | Internal module, do not import or use.
module Data.Generics.Uniplate.Internal.Utils(
    unsafeCoerce, builder, unsafePerformIO, inlinePerformIO, concatCont, SPEC(SPEC)
    ) where

import System.IO.Unsafe(unsafePerformIO)
import Unsafe.Coerce(unsafeCoerce)

import GHC.Exts(build, realWorld#)
import GHC.IO(IO(IO))
import GHC.Types(SPEC(..))


{-# INLINE builder #-}
-- | GHCs @foldr@\/@build@ system, but on all platforms
builder :: forall a . (forall b . (a -> b -> b) -> b -> b) -> [a]
builder :: (forall b. (a -> b -> b) -> b -> b) -> [a]
builder = (forall b. (a -> b -> b) -> b -> b) -> [a]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build


{-# INLINE inlinePerformIO #-}
-- | 'unsafePerformIO', but suitable for inlining. Copied from "Data.ByteString.Base".
inlinePerformIO :: IO a -> a
inlinePerformIO :: IO a -> a
inlinePerformIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) = case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
realWorld# of (# State# RealWorld
_, a
r #) -> a
r


{-# INLINE concatCont #-}
-- | Perform concatentation of continuations
concatCont :: [a -> a] -> a -> a
concatCont :: [a -> a] -> a -> a
concatCont [a -> a]
xs a
rest = ((a -> a) -> a -> a) -> a -> [a -> a] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
($) a
rest [a -> a]
xs