summaryrefslogtreecommitdiff
path: root/standalone/no-th/haskell-patches/reflection_remove-TH.patch
diff options
context:
space:
mode:
Diffstat (limited to 'standalone/no-th/haskell-patches/reflection_remove-TH.patch')
-rw-r--r--standalone/no-th/haskell-patches/reflection_remove-TH.patch134
1 files changed, 40 insertions, 94 deletions
diff --git a/standalone/no-th/haskell-patches/reflection_remove-TH.patch b/standalone/no-th/haskell-patches/reflection_remove-TH.patch
index 7c63f05fc..4f8b4bc20 100644
--- a/standalone/no-th/haskell-patches/reflection_remove-TH.patch
+++ b/standalone/no-th/haskell-patches/reflection_remove-TH.patch
@@ -1,17 +1,17 @@
-From 22c68b43dce437b3c22956f5a968f1b886e60e0c Mon Sep 17 00:00:00 2001
-From: Joey Hess <joey@kitenet.net>
-Date: Tue, 17 Dec 2013 19:15:16 +0000
+From c0f5dcfd6ba7a05bb84b6adc4664c8dde109e6ac Mon Sep 17 00:00:00 2001
+From: dummy <dummy@example.com>
+Date: Fri, 7 Mar 2014 04:30:22 +0000
Subject: [PATCH] remove TH
---
- fast/Data/Reflection.hs | 80 +------------------------------------------------
- 1 file changed, 1 insertion(+), 79 deletions(-)
+ fast/Data/Reflection.hs | 8 +++++---
+ 1 file changed, 5 insertions(+), 3 deletions(-)
diff --git a/fast/Data/Reflection.hs b/fast/Data/Reflection.hs
-index 119d773..cf99efa 100644
+index ca57d35..d3f8356 100644
--- a/fast/Data/Reflection.hs
+++ b/fast/Data/Reflection.hs
-@@ -58,7 +58,7 @@ module Data.Reflection
+@@ -59,7 +59,7 @@ module Data.Reflection
, Given(..)
, give
-- * Template Haskell reflection
@@ -20,94 +20,40 @@ index 119d773..cf99efa 100644
-- * Useful compile time naturals
, Z, D, SD, PD
) where
-@@ -151,87 +151,9 @@ instance Reifies n Int => Reifies (PD n) Int where
- reflect = (\n -> n + n - 1) <$> retagPD reflect
- {-# INLINE reflect #-}
-
---- | This can be used to generate a template haskell splice for a type level version of a given 'int'.
----
---- This does not use GHC TypeLits, instead it generates a numeric type by hand similar to the ones used
---- in the \"Functional Pearl: Implicit Configurations\" paper by Oleg Kiselyov and Chung-Chieh Shan.
--int :: Int -> TypeQ
--int n = case quotRem n 2 of
-- (0, 0) -> conT ''Z
-- (q,-1) -> conT ''PD `appT` int q
-- (q, 0) -> conT ''D `appT` int q
-- (q, 1) -> conT ''SD `appT` int q
-- _ -> error "ghc is bad at math"
--
---- | This is a restricted version of 'int' that can only generate natural numbers. Attempting to generate
---- a negative number results in a compile time error. Also the resulting sequence will consist entirely of
---- Z, D, and SD constructors representing the number in zeroless binary.
--nat :: Int -> TypeQ
--nat n
-- | n >= 0 = int n
-- | otherwise = error "nat: negative"
--
--#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL < 704
--instance Show (Q a)
--instance Eq (Q a)
--#endif
--instance Num a => Num (Q a) where
-- (+) = liftM2 (+)
-- (*) = liftM2 (*)
-- (-) = liftM2 (-)
-- negate = fmap negate
-- abs = fmap abs
-- signum = fmap signum
-- fromInteger = return . fromInteger
+@@ -161,6 +161,7 @@ instance Reifies n Int => Reifies (PD n) Int where
+ -- instead of @$(int 3)@. Sometimes the two will produce the same
+ -- representation (if compiled without the @-DUSE_TYPE_LITS@ preprocessor
+ -- directive).
++{-
+ int :: Int -> TypeQ
+ int n = case quotRem n 2 of
+ (0, 0) -> conT ''Z
+@@ -176,7 +177,7 @@ nat :: Int -> TypeQ
+ nat n
+ | n >= 0 = int n
+ | otherwise = error "nat: negative"
-
--instance Fractional a => Fractional (Q a) where
-- (/) = liftM2 (/)
-- recip = fmap recip
-- fromRational = return . fromRational
--
---- | This permits the use of $(5) as a type splice.
--instance Num Type where
--#ifdef USE_TYPE_LITS
-- a + b = AppT (AppT (VarT ''(+)) a) b
-- a * b = AppT (AppT (VarT ''(*)) a) b
--#if MIN_VERSION_base(4,8,0)
-- a - b = AppT (AppT (VarT ''(-)) a) b
--#else
-- (-) = error "Type.(-): undefined"
--#endif
-- fromInteger = LitT . NumTyLit
--#else
-- (+) = error "Type.(+): undefined"
-- (*) = error "Type.(*): undefined"
-- (-) = error "Type.(-): undefined"
-- fromInteger n = case quotRem n 2 of
-- (0, 0) -> ConT ''Z
-- (q,-1) -> ConT ''PD `AppT` fromInteger q
-- (q, 0) -> ConT ''D `AppT` fromInteger q
-- (q, 1) -> ConT ''SD `AppT` fromInteger q
-- _ -> error "ghc is bad at math"
--#endif
-- abs = error "Type.abs"
-- signum = error "Type.signum"
--
- plus, times, minus :: Num a => a -> a -> a
- plus = (+)
- times = (*)
- minus = (-)
- fract :: Fractional a => a -> a -> a
- fract = (/)
--
---- | This permits the use of $(5) as an expression splice.
--instance Num Exp where
-- a + b = AppE (AppE (VarE 'plus) a) b
-- a * b = AppE (AppE (VarE 'times) a) b
-- a - b = AppE (AppE (VarE 'minus) a) b
-- negate = AppE (VarE 'negate)
-- signum = AppE (VarE 'signum)
-- abs = AppE (VarE 'abs)
-- fromInteger = LitE . IntegerL
++-}
+ #if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL < 704
+ instance Show (Q a)
+ instance Eq (Q a)
+@@ -195,6 +196,7 @@ instance Fractional a => Fractional (Q a) where
+ recip = fmap recip
+ fromRational = return . fromRational
+
++{-
+ -- | This permits the use of $(5) as a type splice.
+ instance Num Type where
+ #ifdef USE_TYPE_LITS
+@@ -254,7 +256,7 @@ instance Num Exp where
+ abs = onProxyType1 abs
+ signum = onProxyType1 signum
+ fromInteger n = ConE 'Proxy `SigE` (ConT ''Proxy `AppT` fromInteger n)
-
--instance Fractional Exp where
-- a / b = AppE (AppE (VarE 'fract) a) b
-- recip = AppE (VarE 'recip)
-- fromRational = LitE . RationalL
++-}
+ #ifdef USE_TYPE_LITS
+ addProxy :: Proxy a -> Proxy b -> Proxy (a + b)
+ addProxy _ _ = Proxy
--
-1.8.5.1
+1.9.0