From 8e6a30359e5af2f6c594db3ddc333c0f4ef8525e Mon Sep 17 00:00:00 2001
From: Rinat Striungis <rinat.stryungis@serokell.io>
Date: Thu, 4 Jun 2020 05:33:30 -0400
Subject: [PATCH] Added "TypeLitChar" to the instance of Binary for TypeLitSort

---
 src/Data/Binary/Class.hs | 11 ++++++++++-
 1 file changed, 10 insertions(+), 1 deletion(-)

diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index a3d3878..975ef7e 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -9,6 +9,10 @@
 {-# LANGUAGE PolyKinds #-}
 #endif
 
+#if MIN_VERSION_base(4,15,0)
+#define HAS_TYPELITS_CHAR
+#endif
+
 #if MIN_VERSION_base(4,8,0)
 #define HAS_NATURAL
 #define HAS_VOID
@@ -960,11 +964,17 @@ instance Binary KindRep where
 instance Binary TypeLitSort where
     put TypeLitSymbol = putWord8 0
     put TypeLitNat = putWord8 1
+#ifdef HAS_TYPELITS_CHAR
+    put TypeLitChar = putWord8 2 
+#endif
     get = do
         tag <- getWord8
         case tag of
           0 -> pure TypeLitSymbol
           1 -> pure TypeLitNat
+#ifdef HAS_TYPELITS_CHAR
+          2 -> pure TypeLitChar 
+#endif
           _ -> fail "GHCi.TH.Binary.putTypeLitSort: invalid tag"
 
 putTypeRep :: TypeRep a -> Put
@@ -1044,4 +1054,3 @@ instance Binary SomeTypeRep where
     put (SomeTypeRep rep) = putTypeRep rep
     get = getSomeTypeRep
 #endif
-
-- 
GitLab