diff --git a/inline-r/src/Foreign/R/Type.hsc b/inline-r/src/Foreign/R/Type.hsc index 9cdb630c..882ed991 100644 --- a/inline-r/src/Foreign/R/Type.hsc +++ b/inline-r/src/Foreign/R/Type.hsc @@ -1,6 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveLift #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GADTs #-} #if __GLASGOW_HASKELL__ >= 810 @@ -53,7 +54,6 @@ import Foreign.R.Constraints import Internal.Error import qualified Language.Haskell.TH.Syntax as Hs -import qualified Language.Haskell.TH.Lib as Hs import Data.Singletons.TH @@ -102,7 +102,7 @@ data SEXPTYPE | New | Free | Fun - deriving (Eq, Ord, Show) + deriving (Eq, Ord, Show, Hs.Lift) instance Enum SEXPTYPE where fromEnum Nil = #const NILSXP @@ -167,9 +167,6 @@ instance NFData SEXPTYPE where genSingletons [''SEXPTYPE] -instance Hs.Lift SEXPTYPE where - lift a = [| $(Hs.conE (Hs.mkName $ "Foreign.R.Type." ++ show a)) |] - -- | Used where the R documentation speaks of "pairlists", which are really just -- regular lists. type PairList = List diff --git a/inline-r/src/Language/R/Literal.hs b/inline-r/src/Language/R/Literal.hs index bd4f3443..ab1ff7bd 100644 --- a/inline-r/src/Language/R/Literal.hs +++ b/inline-r/src/Language/R/Literal.hs @@ -144,26 +144,18 @@ mkProtectedSEXPVectorIO ty xs = do instance Literal [R.Logical] 'R.Logical where mkSEXPIO = mkSEXPVectorIO sing . map return fromSEXP (hexp -> Logical v) = SVector.toList v - fromSEXP _ = - failure "fromSEXP" "Logical expected where some other expression appeared." instance Literal [Int32] 'R.Int where mkSEXPIO = mkSEXPVectorIO sing . map return fromSEXP (hexp -> Int v) = SVector.toList v - fromSEXP _ = - failure "fromSEXP" "Int expected where some other expression appeared." instance Literal [Double] 'R.Real where mkSEXPIO = mkSEXPVectorIO sing . map return fromSEXP (hexp -> Real v) = SVector.toList v - fromSEXP _ = - failure "fromSEXP" "Numeric expected where some other expression appeared." instance Literal [Complex Double] 'R.Complex where mkSEXPIO = mkSEXPVectorIO sing . map return fromSEXP (hexp -> Complex v) = SVector.toList v - fromSEXP _ = - failure "fromSEXP" "Complex expected where some other expression appeared." instance Literal [String] 'R.String where mkSEXPIO = @@ -171,8 +163,6 @@ instance Literal [String] 'R.String where map (\str -> GHC.withCString utf8 str (R.mkCharCE R.CE_UTF8)) fromSEXP (hexp -> String v) = map (\(hexp -> Char xs) -> SVector.toString xs) (SVector.toList v) - fromSEXP _ = - failure "fromSEXP" "String expected where some other expression appeared." instance Literal Text 'R.String where mkSEXPIO s = @@ -184,8 +174,6 @@ instance Literal Text 'R.String where [hexp -> Char x] -> SVector.unsafeWithByteString x $ \p -> do pure $ T.decodeUtf8 p _ -> failure "fromSEXP" "Not a singleton vector" - fromSEXP _ = - failure "fromSEXP" "String expected where some other expression appeared." -- | Create a pairlist from an association list. Result is either a pairlist or -- @nilValue@ if the input is the null list. These are two distinct forms. Hence @@ -225,8 +213,6 @@ instance Literal String 'R.String where fromSEXP x@(hexp -> String {}) | [h] <- fromSEXP x = h | otherwise = failure "fromSEXP" "Not a singleton vector." - fromSEXP _ = - failure "fromSEXP" "String expected where some other expression appeared." instance SVector.SVECTOR ty a => Literal (SVector.Vector ty a) ty where mkSEXPIO = return . SVector.toSEXP diff --git a/inline-r/src/Language/R/Matcher.hs b/inline-r/src/Language/R/Matcher.hs index 7d8e3b28..b50a5c5b 100644 --- a/inline-r/src/Language/R/Matcher.hs +++ b/inline-r/src/Language/R/Matcher.hs @@ -294,7 +294,6 @@ getS3Class = charList <$> attribute SString "class" charList :: SEXP s 'R.String -> [String] charList (H.hexp -> String v) = map ((\(Char s) -> SV.toString s) . H.hexp) $ SV.toList v -charList _ = error "Impossible happened." -- | Get 'dim' attribute. dim :: Matcher s [Int] @@ -302,7 +301,6 @@ dim = go <$> attribute SInt "dim" where go :: SEXP s 'R.Int -> [Int] go (H.hexp -> Int v) = fromIntegral <$> SV.toList v - go _ = error "Impossible happened." -- | Get 'dimnames' attribute. dimnames :: Matcher s [[String]] diff --git a/inline-r/src/Language/R/QQ.hs b/inline-r/src/Language/R/QQ.hs index c4a3b376..bbead4c4 100644 --- a/inline-r/src/Language/R/QQ.hs +++ b/inline-r/src/Language/R/QQ.hs @@ -99,7 +99,6 @@ antiSuffix = "_hs" isAnti :: SEXP s 'R.Char -> Bool isAnti (hexp -> Char (Vector.toString -> name)) = antiSuffix `isSuffixOf` name -isAnti _ = error "Impossible" -- | Chop antiquotation variable names to get the corresponding Haskell variable name. chop :: String -> String