Skip to content
Snippets Groups Projects
Commit ad752b42 authored by Daniel Rogozin's avatar Daniel Rogozin
Browse files

the char kind related update (#11342)

parent c85c4e44
No related tags found
No related merge requests found
...@@ -9,6 +9,10 @@ ...@@ -9,6 +9,10 @@
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
#endif #endif
#if MIN_VERSION_base(4,16,0)
#define HAS_TYPELITS_CHAR
#endif
#if MIN_VERSION_base(4,8,0) #if MIN_VERSION_base(4,8,0)
#define HAS_NATURAL #define HAS_NATURAL
#define HAS_VOID #define HAS_VOID
...@@ -960,11 +964,17 @@ instance Binary KindRep where ...@@ -960,11 +964,17 @@ instance Binary KindRep where
instance Binary TypeLitSort where instance Binary TypeLitSort where
put TypeLitSymbol = putWord8 0 put TypeLitSymbol = putWord8 0
put TypeLitNat = putWord8 1 put TypeLitNat = putWord8 1
#ifdef HAS_TYPELITS_CHAR
put TypeLitChar = putWord8 2
#endif
get = do get = do
tag <- getWord8 tag <- getWord8
case tag of case tag of
0 -> pure TypeLitSymbol 0 -> pure TypeLitSymbol
1 -> pure TypeLitNat 1 -> pure TypeLitNat
#ifdef HAS_TYPELITS_CHAR
2 -> pure TypeLitChar
#endif
_ -> fail "GHCi.TH.Binary.putTypeLitSort: invalid tag" _ -> fail "GHCi.TH.Binary.putTypeLitSort: invalid tag"
putTypeRep :: TypeRep a -> Put putTypeRep :: TypeRep a -> Put
...@@ -1044,4 +1054,3 @@ instance Binary SomeTypeRep where ...@@ -1044,4 +1054,3 @@ instance Binary SomeTypeRep where
put (SomeTypeRep rep) = putTypeRep rep put (SomeTypeRep rep) = putTypeRep rep
get = getSomeTypeRep get = getSomeTypeRep
#endif #endif
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment