{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module GHC.BasicTypes.Extra where
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Basic
#else
import BasicTypes
#endif
import Control.DeepSeq
import Data.Binary
import GHC.Generics
#if MIN_VERSION_ghc(9,4,0)
import GHC.Types.SourceText
#endif
#if MIN_VERSION_ghc(9,8,0)
import Data.ByteString
import GHC.Data.FastString
import Unsafe.Coerce
#endif
deriving instance Generic InlineSpec
instance NFData InlineSpec
instance Binary InlineSpec
#if MIN_VERSION_ghc(9,8,0)
deriving instance Generic FastString
instance Binary FastString
instance Binary FastZString where
put = put . fastZStringToByteString
get = unsafeCoerce (get :: Get ByteString)
#endif
#if MIN_VERSION_ghc(9,4,0)
deriving instance Generic SourceText
#if !MIN_VERSION_ghc(9,8,0)
instance NFData SourceText
#endif
instance Binary SourceText
#endif
isNoInline :: InlineSpec -> Bool
isNoInline :: InlineSpec -> Bool
isNoInline NoInline{} = Bool
True
#if MIN_VERSION_ghc(9,4,0)
isNoInline Opaque{} = True
#endif
isNoInline InlineSpec
_ = Bool
False
isOpaque :: InlineSpec -> Bool
#if MIN_VERSION_ghc(9,4,0)
isOpaque Opaque{} = True
#else
isOpaque :: InlineSpec -> Bool
isOpaque NoInline{} = Bool
True
#endif
isOpaque InlineSpec
_ = Bool
False