{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoCUSKs #-}
{-# LANGUAGE NoNamedWildCards #-}
{-# LANGUAGE NoStarIsType #-}
module Variable.R.SEXP where
import Data.Aeson (ToJSON (..))
import Data.Complex (Complex)
import Data.Int (Int32)
import Data.Singletons
import Data.Singletons.TH
import Data.Text (Text, pack)
import Data.Time.Calendar (Day)
import Data.Vector (Vector)
import qualified Data.Vector as V
import qualified Data.Vector.Algorithms.Merge as VA
import GHC.Float
import GHC.ST (runST)
import Type.Reflection (Typeable, typeRep)
import Variable.Constraints
$(singletons [d|data SEXPTYPE = LGLSXP | INTSXP | REALSXP | CPLSXP | STRSXP | VECSXP|])
deriving instance Show SEXPTYPE
deriving instance Eq SEXPTYPE
type family SEXPElem (s :: SEXPTYPE) = h | h -> s where
SEXPElem 'LGLSXP = Bool
SEXPElem 'INTSXP = Int32
SEXPElem 'REALSXP = Double
SEXPElem 'CPLSXP = Complex Double
SEXPElem 'STRSXP = Text
SEXPElem 'VECSXP = (Text, SomeRTypeRep)
type RTypeRep (s :: SEXPTYPE) = Vector (Maybe (SEXPElem s))
type RTypeRepConstraints (s :: SEXPTYPE) = (SingI s, Typeable s, VariableConstraints (SEXPElem s))
data SomeRTypeRep
= forall s. (RTypeRepConstraints s) => SomeRTypeRep (RTypeRep s)
instance Show SomeRTypeRep where
show :: SomeRTypeRep -> String
show (SomeRTypeRep Vector (Maybe (SEXPElem s))
x) = forall a. Show a => a -> String
show Vector (Maybe (SEXPElem s))
x
instance ToJSON SomeRTypeRep where
toJSON :: SomeRTypeRep -> Value
toJSON (SomeRTypeRep Vector (Maybe (SEXPElem s))
x) = forall a. ToJSON a => a -> Value
toJSON Vector (Maybe (SEXPElem s))
x
class AsRTypeRep s a where
as_rtyperep :: a -> RTypeRep s
type AsLogical = AsRTypeRep 'LGLSXP
type AsInteger = AsRTypeRep 'INTSXP
type AsNumeric = AsRTypeRep 'REALSXP
type AsComplex = AsRTypeRep 'CPLSXP
type AsCharacter = AsRTypeRep 'STRSXP
type AsList = AsRTypeRep 'VECSXP
instance AsRTypeRep 'LGLSXP Bool where
as_rtyperep :: Bool -> RTypeRep 'LGLSXP
as_rtyperep = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
instance AsRTypeRep 'LGLSXP (Maybe Bool) where
as_rtyperep :: Maybe Bool -> RTypeRep 'LGLSXP
as_rtyperep = forall a. a -> Vector a
V.singleton
instance AsRTypeRep 'INTSXP Int32 where
as_rtyperep :: Int32 -> RTypeRep 'INTSXP
as_rtyperep = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
instance AsRTypeRep 'INTSXP (Maybe Int32) where
as_rtyperep :: Maybe Int32 -> RTypeRep 'INTSXP
as_rtyperep = forall a. a -> Vector a
V.singleton
instance AsRTypeRep 'REALSXP Double where
as_rtyperep :: Double -> RTypeRep 'REALSXP
as_rtyperep = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
instance AsRTypeRep 'REALSXP (Maybe Double) where
as_rtyperep :: Maybe Double -> RTypeRep 'REALSXP
as_rtyperep = forall a. a -> Vector a
V.singleton
instance AsRTypeRep 'CPLSXP (Complex Double) where
as_rtyperep :: Complex Double -> RTypeRep 'CPLSXP
as_rtyperep = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
instance AsRTypeRep 'CPLSXP (Maybe (Complex Double)) where
as_rtyperep :: Maybe (Complex Double) -> RTypeRep 'CPLSXP
as_rtyperep = forall a. a -> Vector a
V.singleton
instance AsRTypeRep 'STRSXP Text where
as_rtyperep :: Text -> RTypeRep 'STRSXP
as_rtyperep = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
instance AsRTypeRep 'STRSXP (Maybe Text) where
as_rtyperep :: Maybe Text -> RTypeRep 'STRSXP
as_rtyperep = forall a. a -> Vector a
V.singleton
instance AsRTypeRep 'STRSXP String where
as_rtyperep :: String -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack
instance AsRTypeRep 'STRSXP (Maybe String) where
as_rtyperep :: Maybe String -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Int32 where
as_rtyperep :: Int32 -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Int32) where
as_rtyperep :: Maybe Int32 -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Bool where
as_rtyperep :: Bool -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Bool) where
as_rtyperep :: Maybe Bool -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Double where
as_rtyperep :: Double -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Double) where
as_rtyperep :: Maybe Double -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Int where
as_rtyperep :: Int -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Int) where
as_rtyperep :: Maybe Int -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Integer where
as_rtyperep :: Integer -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Integer) where
as_rtyperep :: Maybe Integer -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP Day where
as_rtyperep :: Day -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance AsRTypeRep 'STRSXP (Maybe Day) where
as_rtyperep :: Maybe Day -> RTypeRep 'STRSXP
as_rtyperep = forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'LGLSXP (Vector Bool) where
as_rtyperep :: Vector Bool -> RTypeRep 'LGLSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just
instance AsRTypeRep 'LGLSXP [Bool] where
as_rtyperep :: [Bool] -> RTypeRep 'LGLSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'LGLSXP (Vector (Maybe Bool)) where
as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'LGLSXP
as_rtyperep = forall a. a -> a
id
instance AsRTypeRep 'LGLSXP [Maybe Bool] where
as_rtyperep :: [Maybe Bool] -> RTypeRep 'LGLSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP (Vector Int32) where
as_rtyperep :: Vector Int32 -> RTypeRep 'INTSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just
instance AsRTypeRep 'INTSXP [Int32] where
as_rtyperep :: [Int32] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP (Vector (Maybe Int32)) where
as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'INTSXP
as_rtyperep = forall a. a -> a
id
instance AsRTypeRep 'INTSXP [Maybe Int32] where
as_rtyperep :: [Maybe Int32] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP (Vector Bool) where
as_rtyperep :: Vector Bool -> RTypeRep 'INTSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Bool
b -> if Bool
b then Int32
1 else Int32
0))
instance AsRTypeRep 'INTSXP [Bool] where
as_rtyperep :: [Bool] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP (Vector (Maybe Bool)) where
as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'INTSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
b -> if Bool
b then Int32
1 else Int32
0))
instance AsRTypeRep 'INTSXP [Maybe Bool] where
as_rtyperep :: [Maybe Bool] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'REALSXP (Vector Double) where
as_rtyperep :: Vector Double -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just
instance AsRTypeRep 'REALSXP [Double] where
as_rtyperep :: [Double] -> RTypeRep 'REALSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'REALSXP (Vector (Maybe Double)) where
as_rtyperep :: Vector (Maybe Double) -> RTypeRep 'REALSXP
as_rtyperep = forall a. a -> a
id
instance AsRTypeRep 'REALSXP [Maybe Double] where
as_rtyperep :: [Maybe Double] -> RTypeRep 'REALSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'REALSXP (Vector (Maybe Int32)) where
as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Double
int2Double forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum))
instance AsRTypeRep 'REALSXP (Vector Int32) where
as_rtyperep :: Vector Int32 -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Double
int2Double forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum))
instance AsRTypeRep 'REALSXP (Vector (Maybe Int)) where
as_rtyperep :: Vector (Maybe Int) -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Double
int2Double)
instance AsRTypeRep 'REALSXP (Vector Int) where
as_rtyperep :: Vector Int -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
int2Double)
instance AsRTypeRep 'REALSXP (Vector (Maybe Bool)) where
as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Double
int2Double forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum))
instance AsRTypeRep 'REALSXP (Vector Bool) where
as_rtyperep :: Vector Bool -> RTypeRep 'REALSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Double
int2Double forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum))
instance AsRTypeRep 'CPLSXP (Vector (Complex Double)) where
as_rtyperep :: Vector (Complex Double) -> RTypeRep 'CPLSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just
instance AsRTypeRep 'CPLSXP [Complex Double] where
as_rtyperep :: [Complex Double] -> RTypeRep 'CPLSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'CPLSXP (Vector (Maybe (Complex Double))) where
as_rtyperep :: Vector (Maybe (Complex Double)) -> RTypeRep 'CPLSXP
as_rtyperep = forall a. a -> a
id
instance AsRTypeRep 'CPLSXP [Maybe (Complex Double)] where
as_rtyperep :: [Maybe (Complex Double)] -> RTypeRep 'CPLSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Text) where
as_rtyperep :: Vector Text -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just
instance AsRTypeRep 'STRSXP [Text] where
as_rtyperep :: [Text] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector (Maybe Text)) where
as_rtyperep :: Vector (Maybe Text) -> RTypeRep 'STRSXP
as_rtyperep = forall a. a -> a
id
instance AsRTypeRep 'STRSXP [Maybe Text] where
as_rtyperep :: [Maybe Text] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector String) where
as_rtyperep :: Vector String -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack)
instance AsRTypeRep 'STRSXP [String] where
as_rtyperep :: [String] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector (Maybe String)) where
as_rtyperep :: Vector (Maybe String) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
pack)
instance AsRTypeRep 'STRSXP [Maybe String] where
as_rtyperep :: [Maybe String] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Int32) where
as_rtyperep :: Vector Int32 -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Int32)) where
as_rtyperep :: Vector (Maybe Int32) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Int32] where
as_rtyperep :: [Int32] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Int32] where
as_rtyperep :: [Maybe Int32] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Bool) where
as_rtyperep :: Vector Bool -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Bool)) where
as_rtyperep :: Vector (Maybe Bool) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Bool] where
as_rtyperep :: [Bool] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Bool] where
as_rtyperep :: [Maybe Bool] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Double) where
as_rtyperep :: Vector Double -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Double)) where
as_rtyperep :: Vector (Maybe Double) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Double] where
as_rtyperep :: [Double] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Double] where
as_rtyperep :: [Maybe Double] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Int) where
as_rtyperep :: Vector Int -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Int)) where
as_rtyperep :: Vector (Maybe Int) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Int] where
as_rtyperep :: [Int] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Int] where
as_rtyperep :: [Maybe Int] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Integer) where
as_rtyperep :: Vector Integer -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Integer)) where
as_rtyperep :: Vector (Maybe Integer) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Integer] where
as_rtyperep :: [Integer] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Integer] where
as_rtyperep :: [Maybe Integer] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP (Vector Day) where
as_rtyperep :: Vector Day -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance AsRTypeRep 'STRSXP (Vector (Maybe Day)) where
as_rtyperep :: Vector (Maybe Day) -> RTypeRep 'STRSXP
as_rtyperep = forall a b. (a -> b) -> Vector a -> Vector b
V.map (String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance AsRTypeRep 'STRSXP [Day] where
as_rtyperep :: [Day] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'STRSXP [Maybe Day] where
as_rtyperep :: [Maybe Day] -> RTypeRep 'STRSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
as_listA :: (RTypeRepConstraints s) => Sing s -> RTypeRep s -> RTypeRep 'VECSXP
as_listA :: forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
Sing s -> RTypeRep s -> RTypeRep 'VECSXP
as_listA Sing s
sxp RTypeRep s
rv = case Sing s
sxp of
Sing s
SSEXPTYPE s
SVECSXP -> RTypeRep s
rv
Sing s
_ -> forall a b. (a -> b) -> Vector a -> Vector b
V.map (\(Int
ix, Maybe (SEXPElem s)
v) -> forall a. a -> Maybe a
Just (String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
ix, forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
RTypeRep s -> SomeRTypeRep
SomeRTypeRep forall a b. (a -> b) -> a -> b
$ forall a. a -> Vector a
V.singleton Maybe (SEXPElem s)
v)) (forall a. Vector a -> Vector (Int, a)
V.indexed RTypeRep s
rv)
instance (RTypeRepConstraints s, a ~ SEXPElem s) => AsRTypeRep 'VECSXP (Vector (Maybe a)) where
as_rtyperep :: Vector (Maybe a) -> RTypeRep 'VECSXP
as_rtyperep = forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
Sing s -> RTypeRep s -> RTypeRep 'VECSXP
as_listA (forall {k} (a :: k). SingI a => Sing a
sing @s)
instance (RTypeRepConstraints s, a ~ SEXPElem s) => AsRTypeRep 'VECSXP [a] where
as_rtyperep :: [a] -> RTypeRep 'VECSXP
as_rtyperep = forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
Sing s -> RTypeRep s -> RTypeRep 'VECSXP
as_listA (forall {k} (a :: k). SingI a => Sing a
sing @s) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> Vector a -> Vector b
V.map forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP Integer where
as_rtyperep :: Integer -> RTypeRep 'INTSXP
as_rtyperep Integer
i
| Integer
i forall a. Ord a => a -> a -> Bool
<= Integer
mm Bool -> Bool -> Bool
&& Integer
i forall a. Ord a => a -> a -> Bool
>= Integer
mn = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep (forall a. Num a => Integer -> a
fromInteger Integer
i :: Int32)
| Bool
otherwise = forall a. a -> Vector a
V.singleton forall a. Maybe a
Nothing
where
mm :: Integer
mm = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int32)
mn :: Integer
mn = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: Int32)
instance AsRTypeRep 'INTSXP (Maybe Integer) where
as_rtyperep :: Maybe Integer -> RTypeRep 'INTSXP
as_rtyperep = \case
Maybe Integer
Nothing -> forall a. a -> Vector a
V.singleton forall a. Maybe a
Nothing
Just Integer
ii -> forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep Integer
ii
instance AsRTypeRep 'INTSXP (Vector Integer) where
as_rtyperep :: Vector Integer -> RTypeRep 'INTSXP
as_rtyperep = forall a b. (a -> Vector b) -> Vector a -> Vector b
V.concatMap forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
instance AsRTypeRep 'INTSXP [Integer] where
as_rtyperep :: [Integer] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
instance AsRTypeRep 'INTSXP (Vector (Maybe Integer)) where
as_rtyperep :: Vector (Maybe Integer) -> RTypeRep 'INTSXP
as_rtyperep = forall a b. (a -> Vector b) -> Vector a -> Vector b
V.concatMap forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
instance AsRTypeRep 'INTSXP [Maybe Integer] where
as_rtyperep :: [Maybe Integer] -> RTypeRep 'INTSXP
as_rtyperep = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList
as_logical :: (AsLogical a) => a -> RTypeRep 'LGLSXP
as_logical :: forall a. AsLogical a => a -> RTypeRep 'LGLSXP
as_logical = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
as_integer :: (AsInteger a) => a -> RTypeRep 'INTSXP
as_integer :: forall a. AsInteger a => a -> RTypeRep 'INTSXP
as_integer = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
as_numeric :: (AsNumeric a) => a -> RTypeRep 'REALSXP
as_numeric :: forall a. AsNumeric a => a -> RTypeRep 'REALSXP
as_numeric = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
as_character :: (AsCharacter a) => a -> RTypeRep 'STRSXP
as_character :: forall a. AsCharacter a => a -> RTypeRep 'STRSXP
as_character = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
as_list :: (AsList v) => v -> RTypeRep 'VECSXP
as_list :: forall v. AsList v => v -> RTypeRep 'VECSXP
as_list = forall (s :: SEXPTYPE) a. AsRTypeRep s a => a -> RTypeRep s
as_rtyperep
withSomeRTypeRep :: SomeRTypeRep -> (forall s. (RTypeRepConstraints s) => RTypeRep s -> t) -> t
withSomeRTypeRep :: forall t.
SomeRTypeRep
-> (forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
RTypeRep s -> t)
-> t
withSomeRTypeRep (SomeRTypeRep RTypeRep s
sexp) forall (s :: SEXPTYPE). RTypeRepConstraints s => RTypeRep s -> t
f = forall (s :: SEXPTYPE). RTypeRepConstraints s => RTypeRep s -> t
f RTypeRep s
sexp
summarizeWith :: (RTypeRep s -> Maybe (SEXPElem s')) -> RTypeRep s -> RTypeRep s'
summarizeWith :: forall (s :: SEXPTYPE) (s' :: SEXPTYPE).
(RTypeRep s -> Maybe (SEXPElem s')) -> RTypeRep s -> RTypeRep s'
summarizeWith RTypeRep s -> Maybe (SEXPElem s')
f = forall a. a -> Vector a
V.singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. RTypeRep s -> Maybe (SEXPElem s')
f
sort :: (Ord (SEXPElem s)) => RTypeRep s -> RTypeRep s
sort :: forall (s :: SEXPTYPE).
Ord (SEXPElem s) =>
RTypeRep s -> RTypeRep s
sort = forall a.
(forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
V.modify forall (m :: Type -> Type) (v :: Type -> Type -> Type) e.
(PrimMonad m, MVector v e, Ord e) =>
v (PrimState m) e -> m ()
VA.sort
sortUniq :: (Ord a) => Vector a -> Vector a
sortUniq :: forall a. Ord a => Vector a -> Vector a
sortUniq Vector a
v = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
MVector s a
mv <- forall (m :: Type -> Type) a.
PrimMonad m =>
Vector a -> m (MVector (PrimState m) a)
V.thaw Vector a
v
MVector s a
mv' <- forall (m :: Type -> Type) (v :: Type -> Type -> Type) e.
(PrimMonad m, MVector v e, Ord e) =>
v (PrimState m) e -> m (v (PrimState m) e)
VA.sortUniq MVector s a
mv
forall (m :: Type -> Type) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
V.freeze MVector s a
mv'
singOfRTypeRep :: forall r. (SingI r) => RTypeRep r -> Sing r
singOfRTypeRep :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> Sing r
singOfRTypeRep RTypeRep r
_ = forall {k} (a :: k). SingI a => Sing a
sing @r
sexpTypeOf :: forall (r :: SEXPTYPE). (SingI r) => RTypeRep r -> SEXPTYPE
sexpTypeOf :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> SEXPTYPE
sexpTypeOf RTypeRep r
_ = forall k (a :: k). SingKind k => Sing a -> Demote k
fromSing forall a b. (a -> b) -> a -> b
$ forall {k} (a :: k). SingI a => Sing a
sing @r
sexpTypeOfElem :: forall (r :: SEXPTYPE). (SingI r) => SEXPElem r -> SEXPTYPE
sexpTypeOfElem :: forall (r :: SEXPTYPE). SingI r => SEXPElem r -> SEXPTYPE
sexpTypeOfElem SEXPElem r
_ = forall k (a :: k). SingKind k => Sing a -> Demote k
fromSing forall a b. (a -> b) -> a -> b
$ forall {k} (a :: k). SingI a => Sing a
sing @r
sexpTypeOfErased :: SomeRTypeRep -> SEXPTYPE
sexpTypeOfErased :: SomeRTypeRep -> SEXPTYPE
sexpTypeOfErased = (forall t.
SomeRTypeRep
-> (forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
RTypeRep s -> t)
-> t
`withSomeRTypeRep` forall (r :: SEXPTYPE). SingI r => RTypeRep r -> SEXPTYPE
sexpTypeOf)
showSEXPElemOf :: forall r. (Typeable (SEXPElem r)) => RTypeRep r -> String
showSEXPElemOf :: forall (r :: SEXPTYPE).
Typeable (SEXPElem r) =>
RTypeRep r -> String
showSEXPElemOf RTypeRep r
_ = forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(SEXPElem r)
textSEXPElemOf :: forall r. (Typeable (SEXPElem r)) => RTypeRep r -> Text
textSEXPElemOf :: forall (r :: SEXPTYPE). Typeable (SEXPElem r) => RTypeRep r -> Text
textSEXPElemOf = String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (r :: SEXPTYPE).
Typeable (SEXPElem r) =>
RTypeRep r -> String
showSEXPElemOf
showSEXPTYPEOf :: forall (r :: SEXPTYPE). (SingI r) => RTypeRep r -> String
showSEXPTYPEOf :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> String
showSEXPTYPEOf = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (r :: SEXPTYPE). SingI r => RTypeRep r -> SEXPTYPE
sexpTypeOf
textSEXPTYPEOf :: forall r. (SingI r) => RTypeRep r -> Text
textSEXPTYPEOf :: forall (r :: SEXPTYPE). SingI r => RTypeRep r -> Text
textSEXPTYPEOf = String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (r :: SEXPTYPE). SingI r => RTypeRep r -> String
showSEXPTYPEOf
textSEXPTYPEOfElem :: forall r. (SingI r) => SEXPElem r -> Text
textSEXPTYPEOfElem :: forall (r :: SEXPTYPE). SingI r => SEXPElem r -> Text
textSEXPTYPEOfElem = String -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (r :: SEXPTYPE). SingI r => SEXPElem r -> SEXPTYPE
sexpTypeOfElem
showSEXPTYPEOfErased :: SomeRTypeRep -> String
showSEXPTYPEOfErased :: SomeRTypeRep -> String
showSEXPTYPEOfErased SomeRTypeRep
v = forall t.
SomeRTypeRep
-> (forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
RTypeRep s -> t)
-> t
withSomeRTypeRep SomeRTypeRep
v forall (r :: SEXPTYPE). SingI r => RTypeRep r -> String
showSEXPTYPEOf
textSEXPTYPEOfErased :: SomeRTypeRep -> Text
textSEXPTYPEOfErased :: SomeRTypeRep -> Text
textSEXPTYPEOfErased SomeRTypeRep
v = forall t.
SomeRTypeRep
-> (forall (s :: SEXPTYPE).
RTypeRepConstraints s =>
RTypeRep s -> t)
-> t
withSomeRTypeRep SomeRTypeRep
v forall (r :: SEXPTYPE). SingI r => RTypeRep r -> Text
textSEXPTYPEOf