{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash #-}

module GHC.Char
    ( -- * Utilities
      chr

      -- * Monomorphic equality operators
      -- | See GHC.Classes#matching_overloaded_methods_in_rules
    , eqChar, neChar
    ) where

import GHC.Base
import GHC.Show

-- | The 'Prelude.toEnum' method restricted to the type 'Data.Char.Char'.
chr :: Int -> Char
chr :: Int -> Char
chr i :: Int
i@(I# Int#
i#)
 | Int# -> Bool
isTrue# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Int#
`leWord#` Word#
0x10FFFF##) = Char# -> Char
C# (Int# -> Char#
chr# Int#
i#)
 | Bool
otherwise
    = [Char] -> Char
forall a. [Char] -> a
errorWithoutStackTrace ([Char]
"Prelude.chr: bad argument: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [Char] -> [Char]
showSignedInt (Int# -> Int
I# Int#
9#) Int
i [Char]
"")