Skip to content
Snippets Groups Projects
Commit 67975c84 authored by Ryan Scott's avatar Ryan Scott
Browse files

Remove old constraints, text-builder, th-utilities patches

parent 54e3c961
No related branches found
No related tags found
No related merge requests found
diff --git a/src/Data/Constraint/Nat.hs b/src/Data/Constraint/Nat.hs
index ac1a78f..a49320b 100644
--- a/src/Data/Constraint/Nat.hs
+++ b/src/Data/Constraint/Nat.hs
@@ -77,10 +77,10 @@ magic f = Sub $ unsafeCoerce (Magic Dict) (natVal (Proxy :: Proxy n) `f` natVal
axiom :: forall a b. Dict (a ~ b)
axiom = unsafeCoerce (Dict :: Dict (a ~ a))
-axiomLe :: forall a b. Dict (a <= b)
+axiomLe :: forall (a :: Nat) (b :: Nat). Dict (a <= b)
axiomLe = axiom
-eqLe :: (a ~ b) :- (a <= b)
+eqLe :: forall (a :: Nat) (b :: Nat). (a ~ b) :- (a <= b)
eqLe = Sub Dict
dividesGcd :: forall a b c. (Divides a b, Divides a c) :- Divides a (Gcd b c)
@@ -150,10 +150,10 @@ timesOne :: forall n. Dict ((n * 1) ~ n)
timesOne = Dict
minZero :: forall n. Dict (Min n 0 ~ 0)
-minZero = Dict
+minZero = axiom
maxZero :: forall n. Dict (Max n 0 ~ n)
-maxZero = Dict
+maxZero = axiom
powZero :: forall n. Dict ((n ^ 0) ~ 1)
powZero = Dict
@@ -161,8 +161,8 @@ powZero = Dict
leZero :: forall a. (a <= 0) :- (a ~ 0)
leZero = Sub axiom
-zeroLe :: forall a. Dict (0 <= a)
-zeroLe = Dict
+zeroLe :: forall (a :: Nat). Dict (0 <= a)
+zeroLe = axiom
plusMinusInverse1 :: forall n m. Dict (((m + n) - n) ~ m)
plusMinusInverse1 = axiom
@@ -346,11 +346,11 @@ timesDiv = axiom
-- (<=) is an internal category in the category of constraints.
-leId :: forall a. Dict (a <= a)
+leId :: forall (a :: Nat). Dict (a <= a)
leId = Dict
-leEq :: forall a b. (a <= b, b <= a) :- (a ~ b)
+leEq :: forall (a :: Nat) (b :: Nat). (a <= b, b <= a) :- (a ~ b)
leEq = Sub axiom
-leTrans :: forall a b c. (b <= c, a <= b) :- (a <= c)
+leTrans :: forall (a :: Nat) (b :: Nat) (c :: Nat). (b <= c, a <= b) :- (a <= c)
leTrans = Sub (axiomLe @a @c)
diff --git a/library/Text/Builder/UTF16.hs b/library/Text/Builder/UTF16.hs
index 2478b87..1687b9e 100644
--- a/library/Text/Builder/UTF16.hs
+++ b/library/Text/Builder/UTF16.hs
@@ -12,8 +12,8 @@ type UTF16View =
{-# INLINE char #-}
char :: Char -> UTF16View
-char =
- unicodeCodePoint . ord
+char x =
+ unicodeCodePoint (ord x)
{-# INLINE unicodeCodePoint #-}
unicodeCodePoint :: Int -> UTF16View
diff --git a/src/TH/Utilities.hs b/src/TH/Utilities.hs
index 43f7b2f..ec04bc2 100644
--- a/src/TH/Utilities.hs
+++ b/src/TH/Utilities.hs
@@ -15,9 +15,15 @@ import Language.Haskell.TH
import Language.Haskell.TH.Syntax
-- | Get the 'Name' of a 'TyVarBndr'
+#if MIN_VERSION_template_haskell(2,17,0)
+tyVarBndrName :: TyVarBndr spec -> Name
+tyVarBndrName (PlainTV n _) = n
+tyVarBndrName (KindedTV n _ _) = n
+#else
tyVarBndrName :: TyVarBndr -> Name
tyVarBndrName (PlainTV n) = n
tyVarBndrName (KindedTV n _) = n
+#endif
appsT :: Type -> [Type] -> Type
appsT x [] = x
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