{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE LambdaCase #-}
module DataFrame.Internal.Column where
import qualified Data.ByteString.Char8 as C
import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Vector.Algorithms.Merge as VA
import qualified Data.Vector.Generic as VG
import qualified Data.Vector as VB
import qualified Data.Vector.Mutable as VBM
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
import Control.Monad.ST (runST)
import DataFrame.Internal.Types
import DataFrame.Internal.Parsing
import Data.Int
import Data.Maybe
import Data.Proxy
import Data.Text.Encoding (decodeUtf8Lenient)
import Data.Type.Equality (type (:~:)(Refl), TestEquality (..))
import Data.Typeable (Typeable, cast)
import Data.Word
import Type.Reflection
import Unsafe.Coerce (unsafeCoerce)
import DataFrame.Errors
import Control.Exception (throw)
import Data.Kind (Type, Constraint)
data Column where
BoxedColumn :: Columnable a => VB.Vector a -> Column
UnboxedColumn :: (Columnable a, VU.Unbox a) => VU.Vector a -> Column
OptionalColumn :: Columnable a => VB.Vector (Maybe a) -> Column
data MutableColumn where
MBoxedColumn :: Columnable a => VBM.IOVector a -> MutableColumn
MUnboxedColumn :: (Columnable a, VU.Unbox a) => VUM.IOVector a -> MutableColumn
data TypedColumn a where
TColumn :: Columnable a => Column -> TypedColumn a
unwrapTypedColumn :: TypedColumn a -> Column
unwrapTypedColumn :: forall a. TypedColumn a -> Column
unwrapTypedColumn (TColumn Column
value) = Column
value
isOptional :: Column -> Bool
isOptional :: Column -> Bool
isOptional (OptionalColumn Vector (Maybe a)
column) = Bool
True
isOptional Column
_ = Bool
False
columnVersionString :: Column -> String
columnVersionString :: Column -> String
columnVersionString Column
column = case Column
column of
BoxedColumn Vector a
_ -> String
"Boxed"
UnboxedColumn Vector a
_ -> String
"Unboxed"
OptionalColumn Vector (Maybe a)
_ -> String
"Optional"
columnTypeString :: Column -> String
columnTypeString :: Column -> String
columnTypeString Column
column = case Column
column of
BoxedColumn (Vector a
column :: VB.Vector a) -> TypeRep a -> String
forall a. Show a => a -> String
show (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
UnboxedColumn (Vector a
column :: VU.Vector a) -> TypeRep a -> String
forall a. Show a => a -> String
show (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
OptionalColumn (Vector (Maybe a)
column :: VB.Vector a) -> TypeRep (Maybe a) -> String
forall a. Show a => a -> String
show (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
instance (Show a) => Show (TypedColumn a) where
show :: TypedColumn a -> String
show (TColumn Column
col) = Column -> String
forall a. Show a => a -> String
show Column
col
instance Show Column where
show :: Column -> String
show :: Column -> String
show (BoxedColumn Vector a
column) = Vector a -> String
forall a. Show a => a -> String
show Vector a
column
show (UnboxedColumn Vector a
column) = Vector a -> String
forall a. Show a => a -> String
show Vector a
column
show (OptionalColumn Vector (Maybe a)
column) = Vector (Maybe a) -> String
forall a. Show a => a -> String
show Vector (Maybe a)
column
instance Eq Column where
(==) :: Column -> Column -> Bool
== :: Column -> Column -> Bool
(==) (BoxedColumn (Vector a
a :: VB.Vector t1)) (BoxedColumn (Vector a
b :: VB.Vector t2)) =
case TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t1) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t2) of
Maybe (a :~: a)
Nothing -> Bool
False
Just a :~: a
Refl -> Vector a
a Vector a -> Vector a -> Bool
forall a. Eq a => a -> a -> Bool
== Vector a
Vector a
b
(==) (OptionalColumn (Vector (Maybe a)
a :: VB.Vector t1)) (OptionalColumn (Vector (Maybe a)
b :: VB.Vector t2)) =
case TypeRep (Maybe a)
-> TypeRep (Maybe a) -> Maybe (Maybe a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t1) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t2) of
Maybe (Maybe a :~: Maybe a)
Nothing -> Bool
False
Just Maybe a :~: Maybe a
Refl -> Vector (Maybe a)
a Vector (Maybe a) -> Vector (Maybe a) -> Bool
forall a. Eq a => a -> a -> Bool
== Vector (Maybe a)
Vector (Maybe a)
b
(==) (UnboxedColumn (Vector a
a :: VU.Vector t1)) (UnboxedColumn (Vector a
b :: VU.Vector t2)) =
case TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t1) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @t2) of
Maybe (a :~: a)
Nothing -> Bool
False
Just a :~: a
Refl -> Vector a
a Vector a -> Vector a -> Bool
forall a. Eq a => a -> a -> Bool
== Vector a
Vector a
b
(==) Column
_ Column
_ = Bool
False
class ColumnifyRep (r :: Rep) a where
toColumnRep :: VB.Vector a -> Column
type Columnable a = (Columnable' a, ColumnifyRep (KindOf a) a, UnboxIf a, SBoolI (Unboxable a), SBoolI (Numeric a) )
instance (Columnable a, VU.Unbox a)
=> ColumnifyRep 'RUnboxed a where
toColumnRep :: Vector a -> Column
toColumnRep = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column)
-> (Vector a -> Vector a) -> Vector a -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VU.convert
instance Columnable a
=> ColumnifyRep 'RBoxed a where
toColumnRep :: Vector a -> Column
toColumnRep = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn
instance Columnable a
=> ColumnifyRep 'ROptional (Maybe a) where
toColumnRep :: Vector (Maybe a) -> Column
toColumnRep = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn
fromVector ::
forall a. (Columnable a, ColumnifyRep (KindOf a) a)
=> VB.Vector a -> Column
fromVector :: forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector = forall (r :: Rep) a. ColumnifyRep r a => Vector a -> Column
toColumnRep @(KindOf a)
fromUnboxedVector :: forall a. (Columnable a, VU.Unbox a) => VU.Vector a -> Column
fromUnboxedVector :: forall a. (Columnable a, Unbox a) => Vector a -> Column
fromUnboxedVector = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn
fromList ::
forall a. (Columnable a, ColumnifyRep (KindOf a) a)
=> [a] -> Column
fromList :: forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
[a] -> Column
fromList = forall (r :: Rep) a. ColumnifyRep r a => Vector a -> Column
toColumnRep @(KindOf a) (Vector a -> Column) -> ([a] -> Vector a) -> [a] -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Vector a
forall a. [a] -> Vector a
VB.fromList
mapColumn
:: forall b c.
( Columnable b
, Columnable c
, UnboxIf c)
=> (b -> c)
-> Column
-> Maybe Column
mapColumn :: forall b c.
(Columnable b, Columnable c, UnboxIf c) =>
(b -> c) -> Column -> Maybe Column
mapColumn b -> c
f = \case
BoxedColumn (Vector a
col :: VB.Vector a)
| Just a :~: b
Refl <- TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((b -> c) -> Vector b -> Vector c
forall a b. (a -> b) -> Vector a -> Vector b
VB.map b -> c
f Vector b
Vector a
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
OptionalColumn (Vector (Maybe a)
col :: VB.Vector a)
| Just Maybe a :~: b
Refl <- TypeRep (Maybe a) -> TypeRep b -> Maybe (Maybe a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((b -> c) -> Vector b -> Vector c
forall a b. (a -> b) -> Vector a -> Vector b
VB.map b -> c
f Vector b
Vector (Maybe a)
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
UnboxedColumn (Vector a
col :: VU.Vector a)
| Just a :~: b
Refl <- TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ case forall a. SBoolI (Unboxable a) => SBool (Unboxable a)
sUnbox @c of
SBool (Unboxable c)
STrue -> Vector c -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn ((b -> c) -> Vector b -> Vector c
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
VU.map b -> c
f Vector b
Vector a
col)
SBool (Unboxable c)
SFalse -> forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((b -> c) -> Vector b -> Vector c
forall a b. (a -> b) -> Vector a -> Vector b
VB.map b -> c
f (Vector b -> Vector b
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector b
Vector a
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
columnLength :: Column -> Int
columnLength :: Column -> Int
columnLength (BoxedColumn Vector a
xs) = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
xs
columnLength (UnboxedColumn Vector a
xs) = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
xs
columnLength (OptionalColumn Vector (Maybe a)
xs) = Vector (Maybe a) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector (Maybe a)
xs
{-# INLINE columnLength #-}
numElements :: Column -> Int
numElements :: Column -> Int
numElements (BoxedColumn Vector a
xs) = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
xs
numElements (UnboxedColumn Vector a
xs) = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
xs
numElements (OptionalColumn Vector (Maybe a)
xs) = (Int -> Maybe a -> Int) -> Int -> Vector (Maybe a) -> Int
forall (v :: * -> *) b a.
Vector v b =>
(a -> b -> a) -> a -> v b -> a
VG.foldl' (\Int
acc Maybe a
x -> Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Maybe a -> Bool
forall a. Maybe a -> Bool
isJust Maybe a
x))) Int
0 Vector (Maybe a)
xs
{-# INLINE numElements #-}
takeColumn :: Int -> Column -> Column
takeColumn :: Int -> Column -> Column
takeColumn Int
n (BoxedColumn Vector a
xs) = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
VG.take Int
n Vector a
xs
takeColumn Int
n (UnboxedColumn Vector a
xs) = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
VG.take Int
n Vector a
xs
takeColumn Int
n (OptionalColumn Vector (Maybe a)
xs) = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Vector (Maybe a) -> Vector (Maybe a)
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
VG.take Int
n Vector (Maybe a)
xs
{-# INLINE takeColumn #-}
takeLastColumn :: Int -> Column -> Column
takeLastColumn :: Int -> Column -> Column
takeLastColumn Int
n Column
column = Int -> Int -> Column -> Column
sliceColumn (Column -> Int
columnLength Column
column Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) Int
n Column
column
{-# INLINE takeLastColumn #-}
sliceColumn :: Int -> Int -> Column -> Column
sliceColumn :: Int -> Int -> Column -> Column
sliceColumn Int
start Int
n (BoxedColumn Vector a
xs) = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
Int -> Int -> v a -> v a
VG.slice Int
start Int
n Vector a
xs
sliceColumn Int
start Int
n (UnboxedColumn Vector a
xs) = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
Int -> Int -> v a -> v a
VG.slice Int
start Int
n Vector a
xs
sliceColumn Int
start Int
n (OptionalColumn Vector (Maybe a)
xs) = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector (Maybe a) -> Vector (Maybe a)
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
Int -> Int -> v a -> v a
VG.slice Int
start Int
n Vector (Maybe a)
xs
{-# INLINE sliceColumn #-}
atIndices :: S.Set Int -> Column -> Column
atIndices :: Set Int -> Column -> Column
atIndices Set Int
indexes (BoxedColumn Vector a
column) = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
VG.ifilter (\Int
i a
_ -> Int
i Int -> Set Int -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set Int
indexes) Vector a
column
atIndices Set Int
indexes (OptionalColumn Vector (Maybe a)
column) = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ (Int -> Maybe a -> Bool) -> Vector (Maybe a) -> Vector (Maybe a)
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
VG.ifilter (\Int
i Maybe a
_ -> Int
i Int -> Set Int -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set Int
indexes) Vector (Maybe a)
column
atIndices Set Int
indexes (UnboxedColumn Vector a
column) = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
VG.ifilter (\Int
i a
_ -> Int
i Int -> Set Int -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set Int
indexes) Vector a
column
{-# INLINE atIndices #-}
atIndicesStable :: VU.Vector Int -> Column -> Column
atIndicesStable :: Vector Int -> Column -> Column
atIndicesStable Vector Int
indexes (BoxedColumn Vector a
column) = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Vector Int
indexes Vector Int -> Vector a -> Vector a
forall a. Vector Int -> Vector a -> Vector a
`getIndices` Vector a
column
atIndicesStable Vector Int
indexes (UnboxedColumn Vector a
column) = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Vector Int
indexes Vector Int -> Vector a -> Vector a
forall a. Unbox a => Vector Int -> Vector a -> Vector a
`getIndicesUnboxed` Vector a
column
atIndicesStable Vector Int
indexes (OptionalColumn Vector (Maybe a)
column) = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Vector Int
indexes Vector Int -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Vector Int -> Vector a -> Vector a
`getIndices` Vector (Maybe a)
column
{-# INLINE atIndicesStable #-}
getIndices :: VU.Vector Int -> VB.Vector a -> VB.Vector a
getIndices :: forall a. Vector Int -> Vector a -> Vector a
getIndices Vector Int
indices Vector a
xs = Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
VB.generate (Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Int
indices) (\Int
i -> Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
VB.! (Vector Int
indices Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
VU.! Int
i))
{-# INLINE getIndices #-}
getIndicesUnboxed :: (VU.Unbox a) => VU.Vector Int -> VU.Vector a -> VU.Vector a
getIndicesUnboxed :: forall a. Unbox a => Vector Int -> Vector a -> Vector a
getIndicesUnboxed Vector Int
indices Vector a
xs = Int -> (Int -> a) -> Vector a
forall a. Unbox a => Int -> (Int -> a) -> Vector a
VU.generate (Vector Int -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Int
indices) (\Int
i -> Vector a
xs Vector a -> Int -> a
forall a. Unbox a => Vector a -> Int -> a
VU.! (Vector Int
indices Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
VU.! Int
i))
{-# INLINE getIndicesUnboxed #-}
findIndices :: forall a. (Columnable a)
=> (a -> Bool)
-> Column
-> Maybe (VU.Vector Int)
findIndices :: forall a.
Columnable a =>
(a -> Bool) -> Column -> Maybe (Vector Int)
findIndices a -> Bool
pred (BoxedColumn (Vector a
column :: VB.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
Vector Int -> Maybe (Vector Int)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector Int -> Maybe (Vector Int))
-> Vector Int -> Maybe (Vector Int)
forall a b. (a -> b) -> a -> b
$ Vector Int -> Vector Int
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert ((a -> Bool) -> Vector a -> Vector Int
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
(a -> Bool) -> v a -> v Int
VG.findIndices a -> Bool
pred Vector a
Vector a
column)
findIndices a -> Bool
pred (UnboxedColumn (Vector a
column :: VU.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
Vector Int -> Maybe (Vector Int)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector Int -> Maybe (Vector Int))
-> Vector Int -> Maybe (Vector Int)
forall a b. (a -> b) -> a -> b
$ (a -> Bool) -> Vector a -> Vector Int
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
(a -> Bool) -> v a -> v Int
VG.findIndices a -> Bool
pred Vector a
Vector a
column
findIndices a -> Bool
pred (OptionalColumn (Vector (Maybe a)
column :: VB.Vector (Maybe b))) = do
a :~: Maybe a
Refl <- TypeRep a -> TypeRep (Maybe a) -> Maybe (a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(Maybe b))
Vector Int -> Maybe (Vector Int)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector Int -> Maybe (Vector Int))
-> Vector Int -> Maybe (Vector Int)
forall a b. (a -> b) -> a -> b
$ Vector Int -> Vector Int
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert ((a -> Bool) -> Vector a -> Vector Int
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
(a -> Bool) -> v a -> v Int
VG.findIndices a -> Bool
pred Vector a
Vector (Maybe a)
column)
sortedIndexes :: Bool -> Column -> VU.Vector Int
sortedIndexes :: Bool -> Column -> Vector Int
sortedIndexes Bool
asc (BoxedColumn Vector a
column ) = (forall s. ST s (Vector Int)) -> Vector Int
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Vector Int)) -> Vector Int)
-> (forall s. ST s (Vector Int)) -> Vector Int
forall a b. (a -> b) -> a -> b
$ do
MVector s (Int, a)
withIndexes <- Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
VG.thaw (Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a)))
-> Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a))
forall a b. (a -> b) -> a -> b
$ Vector a -> Vector (Int, a)
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a)
VG.indexed Vector a
column
Comparison (Int, a)
-> MVector (PrimState (ST s)) (Int, a) -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e) =>
Comparison e -> v (PrimState m) e -> m ()
VA.sortBy (\(Int
a, a
b) (Int
a', a
b') -> (if Bool
asc then a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare else (a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare) a
b a
b') MVector s (Int, a)
MVector (PrimState (ST s)) (Int, a)
withIndexes
Vector (Int, a)
sorted <- Mutable Vector (PrimState (ST s)) (Int, a)
-> ST s (Vector (Int, a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
VG.unsafeFreeze MVector s (Int, a)
Mutable Vector (PrimState (ST s)) (Int, a)
withIndexes
Vector Int -> ST s (Vector Int)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (Vector Int -> ST s (Vector Int))
-> Vector Int -> ST s (Vector Int)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Int) -> Vector Int
forall a. Unbox a => Int -> (Int -> a) -> Vector a
VU.generate (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
column) (\Int
i -> (Int, a) -> Int
forall a b. (a, b) -> a
fst (Vector (Int, a)
sorted Vector (Int, a) -> Int -> (Int, a)
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i))
sortedIndexes Bool
asc (UnboxedColumn Vector a
column) = (forall s. ST s (Vector Int)) -> Vector Int
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Vector Int)) -> Vector Int)
-> (forall s. ST s (Vector Int)) -> Vector Int
forall a b. (a -> b) -> a -> b
$ do
MVector s (Int, a)
withIndexes <- Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
VG.thaw (Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a)))
-> Vector (Int, a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, a))
forall a b. (a -> b) -> a -> b
$ Vector a -> Vector (Int, a)
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a)
VG.indexed Vector a
column
Comparison (Int, a)
-> MVector (PrimState (ST s)) (Int, a) -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e) =>
Comparison e -> v (PrimState m) e -> m ()
VA.sortBy (\(Int
a, a
b) (Int
a', a
b') -> (if Bool
asc then a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare else (a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare) a
b a
b') MVector s (Int, a)
MVector (PrimState (ST s)) (Int, a)
withIndexes
Vector (Int, a)
sorted <- Mutable Vector (PrimState (ST s)) (Int, a)
-> ST s (Vector (Int, a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
VG.unsafeFreeze MVector s (Int, a)
Mutable Vector (PrimState (ST s)) (Int, a)
withIndexes
Vector Int -> ST s (Vector Int)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (Vector Int -> ST s (Vector Int))
-> Vector Int -> ST s (Vector Int)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Int) -> Vector Int
forall a. Unbox a => Int -> (Int -> a) -> Vector a
VU.generate (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
column) (\Int
i -> (Int, a) -> Int
forall a b. (a, b) -> a
fst (Vector (Int, a)
sorted Vector (Int, a) -> Int -> (Int, a)
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i))
sortedIndexes Bool
asc (OptionalColumn Vector (Maybe a)
column ) = (forall s. ST s (Vector Int)) -> Vector Int
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Vector Int)) -> Vector Int)
-> (forall s. ST s (Vector Int)) -> Vector Int
forall a b. (a -> b) -> a -> b
$ do
MVector s (Int, Maybe a)
withIndexes <- Vector (Int, Maybe a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, Maybe a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
VG.thaw (Vector (Int, Maybe a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, Maybe a)))
-> Vector (Int, Maybe a)
-> ST s (Mutable Vector (PrimState (ST s)) (Int, Maybe a))
forall a b. (a -> b) -> a -> b
$ Vector (Maybe a) -> Vector (Int, Maybe a)
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a)
VG.indexed Vector (Maybe a)
column
Comparison (Int, Maybe a)
-> MVector (PrimState (ST s)) (Int, Maybe a) -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) e.
(PrimMonad m, MVector v e) =>
Comparison e -> v (PrimState m) e -> m ()
VA.sortBy (\(Int
a, Maybe a
b) (Int
a', Maybe a
b') -> (if Bool
asc then Maybe a -> Maybe a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare else (Maybe a -> Maybe a -> Ordering) -> Maybe a -> Maybe a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip Maybe a -> Maybe a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare) Maybe a
b Maybe a
b') MVector s (Int, Maybe a)
MVector (PrimState (ST s)) (Int, Maybe a)
withIndexes
Vector (Int, Maybe a)
sorted <- Mutable Vector (PrimState (ST s)) (Int, Maybe a)
-> ST s (Vector (Int, Maybe a))
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
VG.unsafeFreeze MVector s (Int, Maybe a)
Mutable Vector (PrimState (ST s)) (Int, Maybe a)
withIndexes
Vector Int -> ST s (Vector Int)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (Vector Int -> ST s (Vector Int))
-> Vector Int -> ST s (Vector Int)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Int) -> Vector Int
forall a. Unbox a => Int -> (Int -> a) -> Vector a
VU.generate (Vector (Maybe a) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector (Maybe a)
column) (\Int
i -> (Int, Maybe a) -> Int
forall a b. (a, b) -> a
fst (Vector (Int, Maybe a)
sorted Vector (Int, Maybe a) -> Int -> (Int, Maybe a)
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i))
{-# INLINE sortedIndexes #-}
imapColumn
:: forall b c. (Columnable b, Columnable c)
=> (Int -> b -> c) -> Column -> Maybe Column
imapColumn :: forall b c.
(Columnable b, Columnable c) =>
(Int -> b -> c) -> Column -> Maybe Column
imapColumn Int -> b -> c
f = \case
BoxedColumn (Vector a
col :: VB.Vector a)
| Just a :~: b
Refl <- TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((Int -> b -> c) -> Vector b -> Vector c
forall a b. (Int -> a -> b) -> Vector a -> Vector b
VB.imap Int -> b -> c
f Vector b
Vector a
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
UnboxedColumn (Vector a
col :: VU.Vector a)
| Just a :~: b
Refl <- TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$
case forall a. SBoolI (Unboxable a) => SBool (Unboxable a)
sUnbox @c of
SBool (Unboxable c)
STrue -> Vector c -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn ((Int -> b -> c) -> Vector b -> Vector c
forall a b.
(Unbox a, Unbox b) =>
(Int -> a -> b) -> Vector a -> Vector b
VU.imap Int -> b -> c
f Vector b
Vector a
col)
SBool (Unboxable c)
SFalse -> forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((Int -> b -> c) -> Vector b -> Vector c
forall a b. (Int -> a -> b) -> Vector a -> Vector b
VB.imap Int -> b -> c
f (Vector b -> Vector b
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector b
Vector a
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
OptionalColumn (Vector (Maybe a)
col :: VB.Vector a)
| Just Maybe a :~: b
Refl <- TypeRep (Maybe a) -> TypeRep b -> Maybe (Maybe a :~: b)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
-> Column -> Maybe Column
forall a. a -> Maybe a
Just (forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector @c ((Int -> b -> c) -> Vector b -> Vector c
forall a b. (Int -> a -> b) -> Vector a -> Vector b
VB.imap Int -> b -> c
f Vector b
Vector (Maybe a)
col))
| Bool
otherwise -> Maybe Column
forall a. Maybe a
Nothing
ifilterColumn :: forall a . (Columnable a) => (Int -> a -> Bool) -> Column -> Maybe Column
ifilterColumn :: forall a.
Columnable a =>
(Int -> a -> Bool) -> Column -> Maybe Column
ifilterColumn Int -> a -> Bool
f c :: Column
c@(BoxedColumn (Vector a
column :: VB.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
Column -> Maybe Column
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
VG.ifilter Int -> a -> Bool
f Vector a
Vector a
column
ifilterColumn Int -> a -> Bool
f c :: Column
c@(UnboxedColumn (Vector a
column :: VU.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
Column -> Maybe Column
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
VG.ifilter Int -> a -> Bool
f Vector a
Vector a
column
ifilterColumn Int -> a -> Bool
_ Column
_ = Maybe Column
forall a. Maybe a
Nothing
ifoldrColumn :: forall a b. (Columnable a, Columnable b) => (Int -> a -> b -> b) -> b -> Column -> Maybe b
ifoldrColumn :: forall a b.
(Columnable a, Columnable b) =>
(Int -> a -> b -> b) -> b -> Column -> Maybe b
ifoldrColumn Int -> a -> b -> b
f b
acc c :: Column
c@(BoxedColumn (Vector a
column :: VB.Vector d)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (Int -> a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(Int -> a -> b -> b) -> b -> v a -> b
VG.ifoldr Int -> a -> b -> b
f b
acc Vector a
Vector a
column
ifoldrColumn Int -> a -> b -> b
f b
acc c :: Column
c@(OptionalColumn (Vector (Maybe a)
column :: VB.Vector d)) = do
a :~: Maybe a
Refl <- TypeRep a -> TypeRep (Maybe a) -> Maybe (a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (Int -> a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(Int -> a -> b -> b) -> b -> v a -> b
VG.ifoldr Int -> a -> b -> b
f b
acc Vector a
Vector (Maybe a)
column
ifoldrColumn Int -> a -> b -> b
f b
acc c :: Column
c@(UnboxedColumn (Vector a
column :: VU.Vector d)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (Int -> a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(Int -> a -> b -> b) -> b -> v a -> b
VG.ifoldr Int -> a -> b -> b
f b
acc Vector a
Vector a
column
ifoldlColumn :: forall a b . (Columnable a, Columnable b) => (b -> Int -> a -> b) -> b -> Column -> Maybe b
ifoldlColumn :: forall a b.
(Columnable a, Columnable b) =>
(b -> Int -> a -> b) -> b -> Column -> Maybe b
ifoldlColumn b -> Int -> a -> b
f b
acc c :: Column
c@(BoxedColumn (Vector a
column :: VB.Vector d)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (b -> Int -> a -> b) -> b -> Vector a -> b
forall (v :: * -> *) b a.
Vector v b =>
(a -> Int -> b -> a) -> a -> v b -> a
VG.ifoldl' b -> Int -> a -> b
f b
acc Vector a
Vector a
column
ifoldlColumn b -> Int -> a -> b
f b
acc c :: Column
c@(OptionalColumn (Vector (Maybe a)
column :: VB.Vector d)) = do
a :~: Maybe a
Refl <- TypeRep a -> TypeRep (Maybe a) -> Maybe (a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (b -> Int -> a -> b) -> b -> Vector a -> b
forall (v :: * -> *) b a.
Vector v b =>
(a -> Int -> b -> a) -> a -> v b -> a
VG.ifoldl' b -> Int -> a -> b
f b
acc Vector a
Vector (Maybe a)
column
ifoldlColumn b -> Int -> a -> b
f b
acc c :: Column
c@(UnboxedColumn (Vector a
column :: VU.Vector d)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d)
b -> Maybe b
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ (b -> Int -> a -> b) -> b -> Vector a -> b
forall (v :: * -> *) b a.
Vector v b =>
(a -> Int -> b -> a) -> a -> v b -> a
VG.ifoldl' b -> Int -> a -> b
f b
acc Vector a
Vector a
column
headColumn :: forall a . Columnable a => Column -> Maybe a
headColumn :: forall a. Columnable a => Column -> Maybe a
headColumn (BoxedColumn (Vector a
col :: VB.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
a -> Maybe a
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
VG.head Vector a
Vector a
col)
headColumn (UnboxedColumn (Vector a
col :: VU.Vector b)) = do
a :~: a
Refl <- TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
a -> Maybe a
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
VG.head Vector a
Vector a
col)
headColumn (OptionalColumn (Vector (Maybe a)
col :: VB.Vector b)) = do
a :~: Maybe a
Refl <- TypeRep a -> TypeRep (Maybe a) -> Maybe (a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
a -> Maybe a
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
VG.head Vector a
Vector (Maybe a)
col)
reduceColumn :: forall a b. Columnable a => (a -> b) -> Column -> Maybe b
{-# SPECIALIZE reduceColumn ::
(VU.Vector (Double, Double) -> Double) -> Column -> Maybe Double,
(VU.Vector Double -> Double) -> Column -> Maybe Double #-}
reduceColumn :: forall a b. Columnable a => (a -> b) -> Column -> Maybe b
reduceColumn a -> b
f (BoxedColumn (Vector a
column :: c)) = do
Vector a :~: a
Refl <- TypeRep (Vector a) -> TypeRep a -> Maybe (Vector a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @c) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
b -> Maybe b
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
Vector a
column
reduceColumn a -> b
f (UnboxedColumn (Vector a
column :: c)) = do
Vector a :~: a
Refl <- TypeRep (Vector a) -> TypeRep a -> Maybe (Vector a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @c) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
b -> Maybe b
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
Vector a
column
reduceColumn a -> b
f (OptionalColumn (Vector (Maybe a)
column :: c)) = do
Vector (Maybe a) :~: a
Refl <- TypeRep (Vector (Maybe a))
-> TypeRep a -> Maybe (Vector (Maybe a) :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @c) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
b -> Maybe b
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Maybe b) -> b -> Maybe b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
Vector (Maybe a)
column
{-# INLINE reduceColumn #-}
zipColumns :: Column -> Column -> Column
zipColumns :: Column -> Column -> Column
zipColumns (BoxedColumn Vector a
column) (BoxedColumn Vector a
other) = Vector (a, a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Vector a -> Vector (a, a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip Vector a
column Vector a
other)
zipColumns (BoxedColumn Vector a
column) (UnboxedColumn Vector a
other) = Vector (a, a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Int -> (Int -> (a, a)) -> Vector (a, a)
forall a. Int -> (Int -> a) -> Vector a
VB.generate (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
column) (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
other)) (\Int
i -> (Vector a
column Vector a -> Int -> a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i, Vector a
other Vector a -> Int -> a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i)))
zipColumns (BoxedColumn Vector a
column) (OptionalColumn Vector (Maybe a)
optcolumn) = Vector (a, Maybe a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Vector (Maybe a) -> Vector (a, Maybe a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector a
column) Vector (Maybe a)
optcolumn)
zipColumns (UnboxedColumn Vector a
column) (BoxedColumn Vector a
other) = Vector (a, a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Int -> (Int -> (a, a)) -> Vector (a, a)
forall a. Int -> (Int -> a) -> Vector a
VB.generate (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
column) (Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
other)) (\Int
i -> (Vector a
column Vector a -> Int -> a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i, Vector a
other Vector a -> Int -> a
forall (v :: * -> *) a.
(HasCallStack, Vector v a) =>
v a -> Int -> a
VG.! Int
i)))
zipColumns (UnboxedColumn Vector a
column) (UnboxedColumn Vector a
other) = Vector (a, a) -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Vector a -> Vector (a, a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip Vector a
column Vector a
other)
zipColumns (UnboxedColumn Vector a
column) (OptionalColumn Vector (Maybe a)
optcolumn) = Vector (a, Maybe a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Vector (Maybe a) -> Vector (a, Maybe a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector a
column) Vector (Maybe a)
optcolumn)
zipColumns (OptionalColumn Vector (Maybe a)
optcolumn) (BoxedColumn Vector a
column) = Vector (Maybe a, a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector (Maybe a) -> Vector a -> Vector (Maybe a, a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip Vector (Maybe a)
optcolumn (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector a
column))
zipColumns (OptionalColumn Vector (Maybe a)
optcolumn) (UnboxedColumn Vector a
column) = Vector (Maybe a, a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector (Maybe a) -> Vector a -> Vector (Maybe a, a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip Vector (Maybe a)
optcolumn (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VB.convert Vector a
column))
zipColumns (OptionalColumn Vector (Maybe a)
optcolumn) (OptionalColumn Vector (Maybe a)
optother) = Vector (Maybe a, Maybe a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a, Maybe a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
VG.zip Vector (Maybe a)
optcolumn Vector (Maybe a)
optother)
{-# INLINE zipColumns #-}
zipWithColumns :: forall a b c . (Columnable a, Columnable b, Columnable c) => (a -> b -> c) -> Column -> Column -> Maybe Column
zipWithColumns :: forall a b c.
(Columnable a, Columnable b, Columnable c) =>
(a -> b -> c) -> Column -> Column -> Maybe Column
zipWithColumns a -> b -> c
f (UnboxedColumn (Vector a
column :: VU.Vector d)) (UnboxedColumn (Vector a
other :: VU.Vector e)) = case TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @d) of
Just a :~: a
Refl -> case TypeRep b -> TypeRep a -> Maybe (b :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @e) of
Just b :~: a
Refl -> Column -> Maybe Column
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ case forall a. SBoolI (Unboxable a) => SBool (Unboxable a)
sUnbox @c of
SBool (Unboxable c)
STrue -> Vector c -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
fromUnboxedVector ((a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(a -> b -> c) -> Vector a -> Vector b -> Vector c
VU.zipWith a -> b -> c
f Vector a
Vector a
column Vector b
Vector a
other)
SBool (Unboxable c)
SFalse -> Vector c -> Column
forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector (Vector c -> Column) -> Vector c -> Column
forall a b. (a -> b) -> a -> b
$ (a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
VB.zipWith a -> b -> c
f (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert Vector a
Vector a
column) (Vector b -> Vector b
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert Vector b
Vector a
other)
Maybe (b :~: a)
Nothing -> Maybe Column
forall a. Maybe a
Nothing
Maybe (a :~: a)
Nothing -> Maybe Column
forall a. Maybe a
Nothing
zipWithColumns a -> b -> c
f Column
left Column
right = let
left' :: Vector a
left' = forall a. Columnable a => Column -> Vector a
toVector @a Column
left
right' :: Vector b
right' = forall a. Columnable a => Column -> Vector a
toVector @b Column
right
in Column -> Maybe Column
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Column -> Maybe Column) -> Column -> Maybe Column
forall a b. (a -> b) -> a -> b
$ Vector c -> Column
forall a.
(Columnable a, ColumnifyRep (KindOf a) a) =>
Vector a -> Column
fromVector (Vector c -> Column) -> Vector c -> Column
forall a b. (a -> b) -> a -> b
$ (a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
VB.zipWith a -> b -> c
f Vector a
left' Vector b
right'
{-# INLINE zipWithColumns #-}
writeColumn :: Int -> T.Text -> MutableColumn -> IO (Either T.Text Bool)
writeColumn :: Int -> Text -> MutableColumn -> IO (Either Text Bool)
writeColumn Int
i Text
value (MBoxedColumn (IOVector a
col :: VBM.IOVector a)) = let
in case TypeRep a -> TypeRep Text -> Maybe (a :~: Text)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @T.Text) of
Just a :~: Text
Refl -> (if Text -> Bool
isNullish Text
value
then MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
VBM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
"" IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text Bool
forall a b. a -> Either a b
Left (Text -> Either Text Bool) -> Text -> Either Text Bool
forall a b. (a -> b) -> a -> b
$! Text
value)
else MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
VBM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
Text
value IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Either Text Bool
forall a b. b -> Either a b
Right Bool
True))
Maybe (a :~: Text)
Nothing -> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text Bool
forall a b. a -> Either a b
Left Text
value)
writeColumn Int
i Text
value (MUnboxedColumn (IOVector a
col :: VUM.IOVector a)) =
case TypeRep a -> TypeRep Int -> Maybe (a :~: Int)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @Int) of
Just a :~: Int
Refl -> case HasCallStack => Text -> Maybe Int
Text -> Maybe Int
readInt Text
value of
Just Int
v -> MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
VUM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
Int
v IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Either Text Bool
forall a b. b -> Either a b
Right Bool
True)
Maybe Int
Nothing -> MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
VUM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
0 IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text Bool
forall a b. a -> Either a b
Left Text
value)
Maybe (a :~: Int)
Nothing -> case TypeRep a -> TypeRep Double -> Maybe (a :~: Double)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @Double) of
Maybe (a :~: Double)
Nothing -> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text Bool
forall a b. a -> Either a b
Left (Text -> Either Text Bool) -> Text -> Either Text Bool
forall a b. (a -> b) -> a -> b
$! Text
value)
Just a :~: Double
Refl -> case HasCallStack => Text -> Maybe Double
Text -> Maybe Double
readDouble Text
value of
Just Double
v -> MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
VUM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
Double
v IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Either Text Bool
forall a b. b -> Either a b
Right Bool
True)
Maybe Double
Nothing -> MVector (PrimState IO) a -> Int -> a -> IO ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
VUM.unsafeWrite IOVector a
MVector (PrimState IO) a
col Int
i a
0 IO () -> IO (Either Text Bool) -> IO (Either Text Bool)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either Text Bool -> IO (Either Text Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either Text Bool
forall a b. a -> Either a b
Left (Text -> Either Text Bool) -> Text -> Either Text Bool
forall a b. (a -> b) -> a -> b
$! Text
value)
{-# INLINE writeColumn #-}
freezeColumn' :: [(Int, T.Text)] -> MutableColumn -> IO Column
freezeColumn' :: [(Int, Text)] -> MutableColumn -> IO Column
freezeColumn' [(Int, Text)]
nulls (MBoxedColumn IOVector a
col)
| [(Int, Text)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, Text)]
nulls = Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> IO (Vector a) -> IO Column
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState IO) a -> IO (Vector a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
VB.unsafeFreeze IOVector a
MVector (PrimState IO) a
col
| ((Int, Text) -> Bool) -> [(Int, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Text -> Bool
isNullish (Text -> Bool) -> ((Int, Text) -> Text) -> (Int, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Text) -> Text
forall a b. (a, b) -> b
snd) [(Int, Text)]
nulls = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column)
-> (Vector a -> Vector (Maybe a)) -> Vector a -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> Maybe a) -> Vector a -> Vector (Maybe a)
forall a b. (Int -> a -> b) -> Vector a -> Vector b
VB.imap (\Int
i a
v -> if Int
i Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Int, Text) -> Int) -> [(Int, Text)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Text) -> Int
forall a b. (a, b) -> a
fst [(Int, Text)]
nulls then Maybe a
forall a. Maybe a
Nothing else a -> Maybe a
forall a. a -> Maybe a
Just a
v) (Vector a -> Column) -> IO (Vector a) -> IO Column
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState IO) a -> IO (Vector a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
VB.unsafeFreeze IOVector a
MVector (PrimState IO) a
col
| Bool
otherwise = Vector (Either Text a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector (Either Text a) -> Column)
-> (Vector a -> Vector (Either Text a)) -> Vector a -> Column
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> a -> Either Text a) -> Vector a -> Vector (Either Text a)
forall a b. (Int -> a -> b) -> Vector a -> Vector b
VB.imap (\Int
i a
v -> if Int
i Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Int, Text) -> Int) -> [(Int, Text)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Text) -> Int
forall a b. (a, b) -> a
fst [(Int, Text)]
nulls then Text -> Either Text a
forall a b. a -> Either a b
Left (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (String -> Text
forall a. HasCallStack => String -> a
error String
"") (Int -> [(Int, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
i [(Int, Text)]
nulls)) else a -> Either Text a
forall a b. b -> Either a b
Right a
v) (Vector a -> Column) -> IO (Vector a) -> IO Column
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState IO) a -> IO (Vector a)
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> m (Vector a)
VB.unsafeFreeze IOVector a
MVector (PrimState IO) a
col
freezeColumn' [(Int, Text)]
nulls (MUnboxedColumn IOVector a
col)
| [(Int, Text)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, Text)]
nulls = Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> IO (Vector a) -> IO Column
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState IO) a -> IO (Vector a)
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VU.unsafeFreeze IOVector a
MVector (PrimState IO) a
col
| ((Int, Text) -> Bool) -> [(Int, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Text -> Bool
isNullish (Text -> Bool) -> ((Int, Text) -> Text) -> (Int, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Text) -> Text
forall a b. (a, b) -> b
snd) [(Int, Text)]
nulls = MVector (PrimState IO) a -> IO (Vector a)
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VU.unsafeFreeze IOVector a
MVector (PrimState IO) a
col IO (Vector a) -> (Vector a -> IO Column) -> IO Column
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Vector a
c -> Column -> IO Column
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Column -> IO Column) -> Column -> IO Column
forall a b. (a -> b) -> a -> b
$ Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Maybe a) -> Vector (Maybe a)
forall a. Int -> (Int -> a) -> Vector a
VB.generate (Vector a -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector a
c) (\Int
i -> if Int
i Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Int, Text) -> Int) -> [(Int, Text)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Text) -> Int
forall a b. (a, b) -> a
fst [(Int, Text)]
nulls then Maybe a
forall a. Maybe a
Nothing else a -> Maybe a
forall a. a -> Maybe a
Just (Vector a
c Vector a -> Int -> a
forall a. Unbox a => Vector a -> Int -> a
VU.! Int
i))
| Bool
otherwise = MVector (PrimState IO) a -> IO (Vector a)
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
MVector (PrimState m) a -> m (Vector a)
VU.unsafeFreeze IOVector a
MVector (PrimState IO) a
col IO (Vector a) -> (Vector a -> IO Column) -> IO Column
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Vector a
c -> Column -> IO Column
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Column -> IO Column) -> Column -> IO Column
forall a b. (a -> b) -> a -> b
$ Vector (Either Text a) -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector (Either Text a) -> Column)
-> Vector (Either Text a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Either Text a) -> Vector (Either Text a)
forall a. Int -> (Int -> a) -> Vector a
VB.generate (Vector a -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector a
c) (\Int
i -> if Int
i Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ((Int, Text) -> Int) -> [(Int, Text)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Text) -> Int
forall a b. (a, b) -> a
fst [(Int, Text)]
nulls then Text -> Either Text a
forall a b. a -> Either a b
Left (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (String -> Text
forall a. HasCallStack => String -> a
error String
"") (Int -> [(Int, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Int
i [(Int, Text)]
nulls)) else a -> Either Text a
forall a b. b -> Either a b
Right (Vector a
c Vector a -> Int -> a
forall a. Unbox a => Vector a -> Int -> a
VU.! Int
i))
{-# INLINE freezeColumn' #-}
expandColumn :: Int -> Column -> Column
expandColumn :: Int -> Column -> Column
expandColumn Int
n (OptionalColumn Vector (Maybe a)
col) = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Vector (Maybe a)
col Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> Int -> Maybe a -> Vector (Maybe a)
forall a. Int -> a -> Vector a
VB.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector (Maybe a) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector (Maybe a)
col) Maybe a
forall a. Maybe a
Nothing
expandColumn Int
n column :: Column
column@(BoxedColumn Vector a
col)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ (a -> Maybe a) -> Vector a -> Vector (Maybe a)
forall a b. (a -> b) -> Vector a -> Vector b
VB.map a -> Maybe a
forall a. a -> Maybe a
Just Vector a
col Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> Int -> Maybe a -> Vector (Maybe a)
forall a. Int -> a -> Vector a
VB.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col) Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = Column
column
expandColumn Int
n column :: Column
column@(UnboxedColumn Vector a
col)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ (a -> Maybe a) -> Vector a -> Vector (Maybe a)
forall a b. (a -> b) -> Vector a -> Vector b
VB.map a -> Maybe a
forall a. a -> Maybe a
Just (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VU.convert Vector a
col) Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> Int -> Maybe a -> Vector (Maybe a)
forall a. Int -> a -> Vector a
VB.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col) Maybe a
forall a. Maybe a
Nothing
| Bool
otherwise = Column
column
leftExpandColumn :: Int -> Column -> Column
leftExpandColumn :: Int -> Column -> Column
leftExpandColumn Int
n column :: Column
column@(OptionalColumn Vector (Maybe a)
col)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Vector (Maybe a) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector (Maybe a)
col = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Maybe a -> Vector (Maybe a)
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
VG.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector (Maybe a) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector (Maybe a)
col) Maybe a
forall a. Maybe a
Nothing Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> Vector (Maybe a)
col
| Bool
otherwise = Column
column
leftExpandColumn Int
n column :: Column
column@(BoxedColumn Vector a
col)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Maybe a -> Vector (Maybe a)
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
VG.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col) Maybe a
forall a. Maybe a
Nothing Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> (a -> Maybe a) -> Vector a -> Vector (Maybe a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
VG.map a -> Maybe a
forall a. a -> Maybe a
Just Vector a
col
| Bool
otherwise = Column
column
leftExpandColumn Int
n column :: Column
column@(UnboxedColumn Vector a
col)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col = Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Int -> Maybe a -> Vector (Maybe a)
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
VG.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
VG.length Vector a
col) Maybe a
forall a. Maybe a
Nothing Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> (a -> Maybe a) -> Vector a -> Vector (Maybe a)
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
VG.map a -> Maybe a
forall a. a -> Maybe a
Just (Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VU.convert Vector a
col)
| Bool
otherwise = Column
column
concatColumns :: Column -> Column -> Maybe Column
concatColumns :: Column -> Column -> Maybe Column
concatColumns (OptionalColumn Vector (Maybe a)
left) (OptionalColumn Vector (Maybe a)
right) = case TypeRep (Vector (Maybe a))
-> TypeRep (Vector (Maybe a))
-> Maybe (Vector (Maybe a) :~: Vector (Maybe a))
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (Vector (Maybe a) -> TypeRep (Vector (Maybe a))
forall a. Typeable a => a -> TypeRep a
typeOf Vector (Maybe a)
left) (Vector (Maybe a) -> TypeRep (Vector (Maybe a))
forall a. Typeable a => a -> TypeRep a
typeOf Vector (Maybe a)
right) of
Maybe (Vector (Maybe a) :~: Vector (Maybe a))
Nothing -> Maybe Column
forall a. Maybe a
Nothing
Just Vector (Maybe a) :~: Vector (Maybe a)
Refl -> Column -> Maybe Column
forall a. a -> Maybe a
Just (Vector (Maybe a) -> Column
forall a. Columnable a => Vector (Maybe a) -> Column
OptionalColumn (Vector (Maybe a) -> Column) -> Vector (Maybe a) -> Column
forall a b. (a -> b) -> a -> b
$ Vector (Maybe a)
left Vector (Maybe a) -> Vector (Maybe a) -> Vector (Maybe a)
forall a. Semigroup a => a -> a -> a
<> Vector (Maybe a)
Vector (Maybe a)
right)
concatColumns (BoxedColumn Vector a
left) (BoxedColumn Vector a
right) = case TypeRep (Vector a)
-> TypeRep (Vector a) -> Maybe (Vector a :~: Vector a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (Vector a -> TypeRep (Vector a)
forall a. Typeable a => a -> TypeRep a
typeOf Vector a
left) (Vector a -> TypeRep (Vector a)
forall a. Typeable a => a -> TypeRep a
typeOf Vector a
right) of
Maybe (Vector a :~: Vector a)
Nothing -> Maybe Column
forall a. Maybe a
Nothing
Just Vector a :~: Vector a
Refl -> Column -> Maybe Column
forall a. a -> Maybe a
Just (Vector a -> Column
forall a. Columnable a => Vector a -> Column
BoxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Vector a
left Vector a -> Vector a -> Vector a
forall a. Semigroup a => a -> a -> a
<> Vector a
Vector a
right)
concatColumns (UnboxedColumn Vector a
left) (UnboxedColumn Vector a
right) = case TypeRep (Vector a)
-> TypeRep (Vector a) -> Maybe (Vector a :~: Vector a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (Vector a -> TypeRep (Vector a)
forall a. Typeable a => a -> TypeRep a
typeOf Vector a
left) (Vector a -> TypeRep (Vector a)
forall a. Typeable a => a -> TypeRep a
typeOf Vector a
right) of
Maybe (Vector a :~: Vector a)
Nothing -> Maybe Column
forall a. Maybe a
Nothing
Just Vector a :~: Vector a
Refl -> Column -> Maybe Column
forall a. a -> Maybe a
Just (Vector a -> Column
forall a. (Columnable a, Unbox a) => Vector a -> Column
UnboxedColumn (Vector a -> Column) -> Vector a -> Column
forall a b. (a -> b) -> a -> b
$ Vector a
left Vector a -> Vector a -> Vector a
forall a. Semigroup a => a -> a -> a
<> Vector a
Vector a
right)
concatColumns Column
_ Column
_ = Maybe Column
forall a. Maybe a
Nothing
toVector :: forall a . Columnable a => Column -> VB.Vector a
toVector :: forall a. Columnable a => Column -> Vector a
toVector Column
xs = case Column -> Either DataFrameException (Vector a)
forall a (v :: * -> *).
(Vector v a, Columnable a) =>
Column -> Either DataFrameException (v a)
toVectorSafe Column
xs of
Left DataFrameException
err -> DataFrameException -> Vector a
forall a e. Exception e => e -> a
throw DataFrameException
err
Right Vector a
val -> Vector a
val
toList :: forall a . Columnable a => Column -> [a]
toList :: forall a. Columnable a => Column -> [a]
toList Column
xs = case forall a (v :: * -> *).
(Vector v a, Columnable a) =>
Column -> Either DataFrameException (v a)
toVectorSafe @a Column
xs of
Left DataFrameException
err -> DataFrameException -> [a]
forall a e. Exception e => e -> a
throw DataFrameException
err
Right Vector a
val -> Vector a -> [a]
forall a. Vector a -> [a]
VB.toList Vector a
val
toVectorSafe :: forall a v . (VG.Vector v a, Columnable a) => Column -> Either DataFrameException (v a)
toVectorSafe :: forall a (v :: * -> *).
(Vector v a, Columnable a) =>
Column -> Either DataFrameException (v a)
toVectorSafe column :: Column
column@(OptionalColumn (Vector (Maybe a)
col :: VB.Vector b)) =
case TypeRep a -> TypeRep (Maybe a) -> Maybe (a :~: Maybe a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b) of
Just a :~: Maybe a
Refl -> v a -> Either DataFrameException (v a)
forall a b. b -> Either a b
Right (v a -> Either DataFrameException (v a))
-> v a -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ Vector a -> v a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert Vector a
Vector (Maybe a)
col
Maybe (a :~: Maybe a)
Nothing -> DataFrameException -> Either DataFrameException (v a)
forall a b. a -> Either a b
Left (DataFrameException -> Either DataFrameException (v a))
-> DataFrameException -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ TypeErrorContext a (Maybe a) -> DataFrameException
forall a b.
(Typeable a, Typeable b) =>
TypeErrorContext a b -> DataFrameException
TypeMismatchException (MkTypeErrorContext { userType :: Either String (TypeRep a)
userType = TypeRep a -> Either String (TypeRep a)
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
, expectedType :: Either String (TypeRep (Maybe a))
expectedType = TypeRep (Maybe a) -> Either String (TypeRep (Maybe a))
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
, callingFunctionName :: Maybe String
callingFunctionName = String -> Maybe String
forall a. a -> Maybe a
Just String
"toVectorSafe"
, errorColumnName :: Maybe String
errorColumnName = Maybe String
forall a. Maybe a
Nothing})
toVectorSafe (BoxedColumn (Vector a
col :: VB.Vector b)) =
case TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b) of
Just a :~: a
Refl -> v a -> Either DataFrameException (v a)
forall a b. b -> Either a b
Right (v a -> Either DataFrameException (v a))
-> v a -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ Vector a -> v a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert Vector a
Vector a
col
Maybe (a :~: a)
Nothing -> DataFrameException -> Either DataFrameException (v a)
forall a b. a -> Either a b
Left (DataFrameException -> Either DataFrameException (v a))
-> DataFrameException -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ TypeErrorContext a a -> DataFrameException
forall a b.
(Typeable a, Typeable b) =>
TypeErrorContext a b -> DataFrameException
TypeMismatchException (MkTypeErrorContext { userType :: Either String (TypeRep a)
userType = TypeRep a -> Either String (TypeRep a)
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
, expectedType :: Either String (TypeRep a)
expectedType = TypeRep a -> Either String (TypeRep a)
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
, callingFunctionName :: Maybe String
callingFunctionName = String -> Maybe String
forall a. a -> Maybe a
Just String
"toVectorSafe"
, errorColumnName :: Maybe String
errorColumnName = Maybe String
forall a. Maybe a
Nothing})
toVectorSafe (UnboxedColumn (Vector a
col :: VU.Vector b)) =
case TypeRep a -> TypeRep a -> Maybe (a :~: a)
forall a b. TypeRep a -> TypeRep b -> Maybe (a :~: b)
forall {k} (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
testEquality (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a) (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b) of
Just a :~: a
Refl -> v a -> Either DataFrameException (v a)
forall a b. b -> Either a b
Right (v a -> Either DataFrameException (v a))
-> v a -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ Vector a -> v a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
VG.convert Vector a
Vector a
col
Maybe (a :~: a)
Nothing -> DataFrameException -> Either DataFrameException (v a)
forall a b. a -> Either a b
Left (DataFrameException -> Either DataFrameException (v a))
-> DataFrameException -> Either DataFrameException (v a)
forall a b. (a -> b) -> a -> b
$ TypeErrorContext a a -> DataFrameException
forall a b.
(Typeable a, Typeable b) =>
TypeErrorContext a b -> DataFrameException
TypeMismatchException (MkTypeErrorContext { userType :: Either String (TypeRep a)
userType = TypeRep a -> Either String (TypeRep a)
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @a)
, expectedType :: Either String (TypeRep a)
expectedType = TypeRep a -> Either String (TypeRep a)
forall a b. b -> Either a b
Right (forall a. Typeable a => TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep @b)
, callingFunctionName :: Maybe String
callingFunctionName = String -> Maybe String
forall a. a -> Maybe a
Just String
"toVectorSafe"
, errorColumnName :: Maybe String
errorColumnName = Maybe String
forall a. Maybe a
Nothing})