Safe Haskell | None |
---|---|
Language | Haskell2010 |
DataFrame
Synopsis
- fromList :: [(Text, Column)] -> DataFrame
- apply :: (Columnable b, Columnable c) => (b -> c) -> Text -> DataFrame -> DataFrame
- data Rep
- data RowValue where
- Value :: forall a. Columnable' a => a -> RowValue
- empty :: DataFrame
- data Expr a where
- Col :: forall a. Columnable a => Text -> Expr a
- Lit :: forall a. Columnable a => a -> Expr a
- Apply :: forall a b. (Columnable a, Columnable b) => Text -> (b -> a) -> Expr b -> Expr a
- BinOp :: forall c b a. (Columnable c, Columnable b, Columnable a) => Text -> (c -> b -> a) -> Expr c -> Expr b -> Expr a
- null :: DataFrame -> Bool
- filter :: Columnable a => Text -> (a -> Bool) -> DataFrame -> DataFrame
- defaultOptions :: ReadOptions
- lift :: (Columnable a, Columnable b) => (a -> b) -> Expr a -> Expr b
- range :: (Int, Int) -> DataFrame -> DataFrame
- take :: Int -> DataFrame -> DataFrame
- data Aggregation
- groupBy :: [Text] -> DataFrame -> DataFrame
- sortBy :: SortOrder -> [Text] -> DataFrame -> DataFrame
- sum :: Text -> DataFrame -> Maybe Double
- drop :: Int -> DataFrame -> DataFrame
- rotate :: [String] -> [String]
- type family If (cond :: Bool) (yes :: k) (no :: k) :: k where ...
- readInt :: HasCallStack => Text -> Maybe Int
- fold :: (a -> DataFrame -> DataFrame) -> [a] -> DataFrame -> DataFrame
- readInteger :: HasCallStack => Text -> Maybe Integer
- eq :: (Columnable a, Eq a) => Expr a -> Expr a -> Expr Bool
- toVector :: Columnable a => Column -> Vector a
- select :: [Text] -> DataFrame -> DataFrame
- data Column where
- BoxedColumn :: forall a. Columnable a => Vector a -> Column
- UnboxedColumn :: forall a. (Columnable a, Unbox a) => Vector a -> Column
- OptionalColumn :: forall a. Columnable a => Vector (Maybe a) -> Column
- GroupedBoxedColumn :: forall a. Columnable a => Vector (Vector a) -> Column
- GroupedUnboxedColumn :: forall a. (Columnable a, Unbox a) => Vector (Vector a) -> Column
- GroupedOptionalColumn :: forall a. Columnable a => Vector (Vector (Maybe a)) -> Column
- MutableBoxedColumn :: forall a. Columnable a => IOVector a -> Column
- MutableUnboxedColumn :: forall a. (Columnable a, Unbox a) => IOVector a -> Column
- correlation :: Text -> Text -> DataFrame -> Maybe Double
- median :: Text -> DataFrame -> Maybe Double
- variance :: Text -> DataFrame -> Maybe Double
- mean :: Text -> DataFrame -> Maybe Double
- skewness :: Text -> DataFrame -> Maybe Double
- formatNumber :: Double -> String
- clip :: Int -> Int -> Int -> Int
- geq :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- rename :: Text -> Text -> DataFrame -> DataFrame
- selectBy :: (Text -> Bool) -> DataFrame -> DataFrame
- data DataFrame = DataFrame (Vector (Maybe Column)) (Map Text Int) [Int] (Int, Int)
- type Row = Vector RowValue
- mkRowRep :: DataFrame -> Set Text -> Int -> Int
- data DataFrameException where
- TypeMismatchException :: forall a b. (Typeable a, Typeable b) => TypeRep a -> TypeRep b -> Text -> Text -> DataFrameException
- TypeMismatchException' :: forall a. Typeable a => TypeRep a -> String -> Text -> Text -> DataFrameException
- ColumnNotFoundException :: Text -> Text -> [Text] -> DataFrameException
- isNullish :: Text -> Bool
- toColumn' :: (Columnable a, ColumnifyRep (KindOf a) a) => Vector a -> Column
- toColumn :: (Columnable a, ColumnifyRep (KindOf a) a) => [a] -> Column
- columnLength :: Column -> Int
- columnTypeString :: Column -> String
- expandColumn :: Int -> Column -> Column
- type Columnable a = (Columnable' a, ColumnifyRep (KindOf a) a, UnboxIf a, SBoolI (Unboxable a))
- getColumn :: Text -> DataFrame -> Maybe Column
- dimensions :: DataFrame -> (Int, Int)
- mkRowFromArgs :: [Text] -> DataFrame -> Int -> Row
- toRowValue :: Columnable' a => a -> RowValue
- frequencies :: Text -> DataFrame -> DataFrame
- itransform :: (Typeable b, Typeable c, Columnable b, Columnable c) => (Int -> b -> c) -> Column -> Maybe Column
- ifoldrColumn :: (Columnable a, Columnable b) => (Int -> a -> b -> b) -> b -> Column -> Maybe b
- data TypedColumn a where
- TColumn :: forall a. Columnable a => Column -> TypedColumn a
- transform :: (Columnable b, Columnable c, UnboxIf c, Typeable b, Typeable c) => (b -> c) -> Column -> Maybe Column
- unwrapTypedColumn :: TypedColumn a -> Column
- parseDefaults :: Bool -> DataFrame -> DataFrame
- getIndicesUnboxed :: Unbox a => Vector Int -> Vector a -> Vector a
- getIndices :: Vector Int -> Vector a -> Vector a
- freezeColumn' :: [(Int, Text)] -> Column -> IO Column
- writeColumn :: Int -> Text -> Column -> IO (Either Text Bool)
- col :: Columnable a => Text -> Expr a
- data HistogramConfig = HistogramConfig {}
- addCallPointInfo :: Text -> Maybe Text -> String -> String
- typeMismatchError :: TypeRep a -> TypeRep b -> String
- typeMismatchError' :: String -> String -> String
- columnNotFound :: Text -> Text -> [Text] -> String
- guessColumnName :: Text -> [Text] -> Text
- typeAnnotationSuggestion :: String -> String
- editDistance :: Text -> Text -> Int
- readValue :: (HasCallStack, Read a) => Text -> a
- readByteStringInt :: HasCallStack => ByteString -> Maybe Int
- readDouble :: HasCallStack => Text -> Maybe Double
- readIntegerEither :: HasCallStack => Text -> Either Text Integer
- readIntEither :: HasCallStack => Text -> Either Text Int
- readDoubleEither :: HasCallStack => Text -> Either Text Double
- safeReadValue :: Read a => Text -> Maybe a
- readWithDefault :: (HasCallStack, Read a) => a -> Text -> a
- lt :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- gt :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- type Columnable' a = (Typeable a, Show a, Ord a, Eq a)
- isGrouped :: Column -> Bool
- columnVersionString :: Column -> String
- type family Unboxable a :: Bool where ...
- type family KindOf a :: Rep where ...
- class ColumnifyRep (r :: Rep) a where
- toColumnRep :: Vector a -> Column
- type UnboxIf a = When (Unboxable a) (Unbox a)
- class SBoolI (b :: Bool) where
- data SBool (b :: Bool) where
- sUnbox :: SBoolI (Unboxable a) => SBool (Unboxable a)
- type family When (flag :: Bool) c where ...
- toColumnUnboxed :: (Columnable a, Unbox a) => Vector a -> Column
- takeColumn :: Int -> Column -> Column
- takeLastColumn :: Int -> Column -> Column
- sliceColumn :: Int -> Int -> Column -> Column
- atIndices :: Set Int -> Column -> Column
- atIndicesStable :: Vector Int -> Column -> Column
- sortedIndexes :: Bool -> Column -> Vector Int
- ifilterColumn :: Columnable a => (Int -> a -> Bool) -> Column -> Maybe Column
- ifoldlColumn :: (Columnable a, Columnable b) => (b -> Int -> a -> b) -> b -> Column -> Maybe b
- reduceColumn :: Columnable a => (a -> b) -> Column -> b
- safeReduceColumn :: Typeable a => (a -> b) -> Column -> Maybe b
- zipColumns :: Column -> Column -> Column
- zipWithColumns :: (Columnable a, Columnable b, Columnable c) => (a -> b -> c) -> Column -> Column -> Column
- nulls :: Column -> Int
- leq :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- asText :: DataFrame -> Bool -> Text
- initialColumnSize :: Int
- metadata :: DataFrame -> String
- toRowList :: [Text] -> DataFrame -> [Row]
- toRowVector :: [Text] -> DataFrame -> Vector Row
- sortedIndexes' :: Bool -> Vector Row -> Vector Int
- interpret :: forall a b. Columnable a => DataFrame -> Expr a -> TypedColumn a
- lit :: Columnable a => a -> Expr a
- lift2 :: (Columnable c, Columnable b, Columnable a) => (c -> b -> a) -> Expr c -> Expr b -> Expr a
- columnNames :: DataFrame -> [Text]
- insertColumn :: Columnable a => Text -> Vector a -> DataFrame -> DataFrame
- insertColumn' :: Text -> Maybe Column -> DataFrame -> DataFrame
- cloneColumn :: Text -> Text -> DataFrame -> DataFrame
- insertUnboxedColumn :: (Columnable a, Unbox a) => Text -> Vector a -> DataFrame -> DataFrame
- insertColumnWithDefault :: Columnable a => a -> Text -> Vector a -> DataFrame -> DataFrame
- columnSize :: Text -> DataFrame -> Maybe Int
- data ColumnInfo = ColumnInfo {
- nameOfColumn :: !Text
- nonNullValues :: !Int
- nullValues :: !Int
- partiallyParsedValues :: !Int
- uniqueValues :: !Int
- typeOfColumn :: !Text
- columnInfo :: DataFrame -> DataFrame
- partiallyParsed :: Column -> Int
- fromColumnList :: [Column] -> DataFrame
- valueCounts :: Columnable a => Text -> DataFrame -> [(a, Int)]
- data HistogramOrientation
- data PlotColumns
- = PlotAll
- | PlotSubset [Text]
- plotHistograms :: HasCallStack => PlotColumns -> HistogramOrientation -> DataFrame -> IO ()
- plotForColumn :: HasCallStack => Text -> Maybe Column -> HistogramOrientation -> DataFrame -> IO ()
- plotHistogramsBy :: HasCallStack => Text -> PlotColumns -> HistogramOrientation -> DataFrame -> IO ()
- plotForColumnBy :: HasCallStack => Text -> Text -> Maybe Column -> Maybe Column -> HistogramOrientation -> DataFrame -> IO ()
- countOccurrences :: Ord a => Vector a -> [(a, Int)]
- plotGivenCounts' :: HasCallStack => Text -> [((String, String), Int)] -> IO ()
- numericHistogram :: (HasCallStack, Columnable a) => Text -> Vector a -> String
- plotVerticalGivenCounts :: HasCallStack => Text -> [(String, Int)] -> IO ()
- plotGivenCounts :: HasCallStack => Text -> [(String, Int)] -> IO ()
- leftJustify :: String -> Int -> String
- smallestPartition :: Ord a => a -> [a] -> a
- intPlotRanges :: [Int]
- defaultConfig :: HistogramConfig
- createHistogram :: HistogramConfig -> [Double] -> String
- largestPartition :: Ord a => a -> [a] -> a
- calculateBins :: [Double] -> Int -> [(Double, Int)]
- data SortOrder
- applyStatistic :: (Vector Double -> Double) -> Text -> DataFrame -> Maybe Double
- standardDeviation :: Text -> DataFrame -> Maybe Double
- interQuartileRange :: Text -> DataFrame -> Maybe Double
- _getColumnAsDouble :: Text -> DataFrame -> Maybe (Vector Double)
- applyStatistics :: (Vector Double -> Vector Double) -> Text -> DataFrame -> Maybe (Vector Double)
- summarize :: DataFrame -> DataFrame
- derive :: Columnable a => Text -> Expr a -> DataFrame -> DataFrame
- applyMany :: (Columnable b, Columnable c) => (b -> c) -> [Text] -> DataFrame -> DataFrame
- applyInt :: Columnable b => (Int -> b) -> Text -> DataFrame -> DataFrame
- applyDouble :: Columnable b => (Double -> b) -> Text -> DataFrame -> DataFrame
- applyWhere :: (Columnable a, Columnable b) => (a -> Bool) -> Text -> (b -> b) -> Text -> DataFrame -> DataFrame
- applyAtIndex :: Columnable a => Int -> (a -> a) -> Text -> DataFrame -> DataFrame
- impute :: Columnable b => Text -> b -> DataFrame -> DataFrame
- takeLast :: Int -> DataFrame -> DataFrame
- dropLast :: Int -> DataFrame -> DataFrame
- filterBy :: Columnable a => (a -> Bool) -> Text -> DataFrame -> DataFrame
- filterWhere :: Expr Bool -> DataFrame -> DataFrame
- filterJust :: Text -> DataFrame -> DataFrame
- filterAllJust :: DataFrame -> DataFrame
- cube :: (Int, Int) -> DataFrame -> DataFrame
- selectIntRange :: (Int, Int) -> DataFrame -> DataFrame
- selectRange :: (Text, Text) -> DataFrame -> DataFrame
- exclude :: [Text] -> DataFrame -> DataFrame
- appendWithFrontMin :: Ord a => a -> [a] -> [a]
- groupColumns :: Vector (Vector Int) -> DataFrame -> DataFrame -> Text -> DataFrame
- mkGroupedColumns :: Vector Int -> DataFrame -> DataFrame -> Text -> DataFrame
- hash' :: Columnable a => a -> Double
- groupByAgg :: Aggregation -> [Text] -> DataFrame -> DataFrame
- reduceBy :: (Columnable a, Columnable b) => (forall (v :: Type -> Type). Vector v a => v a -> b) -> Text -> DataFrame -> DataFrame
- reduceByAgg :: Aggregation -> Text -> DataFrame -> DataFrame
- aggregate :: [(Text, Aggregation)] -> DataFrame -> DataFrame
- distinct :: DataFrame -> DataFrame
- data ReadOptions = ReadOptions {}
- parseDefault :: Bool -> Maybe Column -> Maybe Column
- readCsv :: String -> IO DataFrame
- readSeparated :: Char -> ReadOptions -> String -> IO DataFrame
- readTsv :: String -> IO DataFrame
- countRows :: Char -> FilePath -> IO Int
- parseSep :: Char -> Text -> [Text]
- getInitialDataVectors :: Int -> IOVector Column -> [Text] -> IO ()
- fillColumns :: Int -> Char -> IOVector Column -> IOVector [(Int, Text)] -> Handle -> IO ()
- freezeColumn :: IOVector Column -> Vector [(Int, Text)] -> ReadOptions -> Int -> IO (Maybe Column)
- inferValueType :: Text -> Text
- parseRow :: Char -> Parser [Text]
- writeValue :: IOVector Column -> IOVector [(Int, Text)] -> Int -> Int -> Text -> IO ()
- record :: Char -> Parser [Text]
- field :: Char -> Parser Text
- lineEnd :: Parser ()
- quotedField :: Parser Text
- unquotedField :: Char -> Parser Text
- unquotedTerminators :: Char -> Set Char
- writeCsv :: String -> DataFrame -> IO ()
- writeSeparated :: Char -> String -> DataFrame -> IO ()
- getRowAsText :: DataFrame -> Int -> [Text]
- (|>) :: a -> (a -> b) -> b
Documentation
Arguments
:: (Columnable b, Columnable c) | |
=> (b -> c) | function to apply |
-> Text | Column name |
-> DataFrame | DataFrame to apply operation to |
-> DataFrame |
O(k) Apply a function to a given column in a dataframe.
Constructors
Value :: forall a. Columnable' a => a -> RowValue |
Constructors
Col :: forall a. Columnable a => Text -> Expr a | |
Lit :: forall a. Columnable a => a -> Expr a | |
Apply :: forall a b. (Columnable a, Columnable b) => Text -> (b -> a) -> Expr b -> Expr a | |
BinOp :: forall c b a. (Columnable c, Columnable b, Columnable a) => Text -> (c -> b -> a) -> Expr c -> Expr b -> Expr a |
Instances
(Floating a, Columnable a) => Floating (Expr a) Source # | |
(Num a, Columnable a) => Num (Expr a) Source # | |
(Fractional a, Columnable a) => Fractional (Expr a) Source # | |
Show a => Show (Expr a) Source # | |
Arguments
:: Columnable a | |
=> Text | Column to filter by |
-> (a -> Bool) | Filter condition |
-> DataFrame | Dataframe to filter |
-> DataFrame |
O(n * k) Filter rows by a given condition.
filter "x" even df
defaultOptions :: ReadOptions Source #
By default we assume the file has a header, we infer the types on read and we convert any rows with nullish objects into Maybe (safeRead).
lift :: (Columnable a, Columnable b) => (a -> b) -> Expr a -> Expr b Source #
data Aggregation Source #
Instances
Show Aggregation Source # | |
Defined in DataFrame.Operations.Aggregation Methods showsPrec :: Int -> Aggregation -> ShowS # show :: Aggregation -> String # showList :: [Aggregation] -> ShowS # | |
Eq Aggregation Source # | |
Defined in DataFrame.Operations.Aggregation |
groupBy :: [Text] -> DataFrame -> DataFrame Source #
O(k * n) groups the dataframe by the given rows aggregating the remaining rows into vector that should be reduced later.
sortBy :: SortOrder -> [Text] -> DataFrame -> DataFrame Source #
O(k log n) Sorts the dataframe by a given row.
sortBy "Age" df
readInteger :: HasCallStack => Text -> Maybe Integer Source #
toVector :: Columnable a => Column -> Vector a Source #
select :: [Text] -> DataFrame -> DataFrame Source #
O(n) Selects a number of columns in a given dataframe.
select ["name", "age"] df
Our representation of a column is a GADT that can store data in either a vector with boxed elements or
Constructors
BoxedColumn :: forall a. Columnable a => Vector a -> Column | |
UnboxedColumn :: forall a. (Columnable a, Unbox a) => Vector a -> Column | |
OptionalColumn :: forall a. Columnable a => Vector (Maybe a) -> Column | |
GroupedBoxedColumn :: forall a. Columnable a => Vector (Vector a) -> Column | |
GroupedUnboxedColumn :: forall a. (Columnable a, Unbox a) => Vector (Vector a) -> Column | |
GroupedOptionalColumn :: forall a. Columnable a => Vector (Vector (Maybe a)) -> Column | |
MutableBoxedColumn :: forall a. Columnable a => IOVector a -> Column | |
MutableUnboxedColumn :: forall a. (Columnable a, Unbox a) => IOVector a -> Column |
Instances
formatNumber :: Double -> String Source #
selectBy :: (Text -> Bool) -> DataFrame -> DataFrame Source #
O(n) select columns by column predicate name.
data DataFrameException where Source #
Constructors
TypeMismatchException | |
TypeMismatchException' | |
ColumnNotFoundException :: Text -> Text -> [Text] -> DataFrameException |
Instances
Exception DataFrameException Source # | |
Defined in DataFrame.Errors Methods toException :: DataFrameException -> SomeException # fromException :: SomeException -> Maybe DataFrameException # | |
Show DataFrameException Source # | |
Defined in DataFrame.Errors Methods showsPrec :: Int -> DataFrameException -> ShowS # show :: DataFrameException -> String # showList :: [DataFrameException] -> ShowS # |
toColumn' :: (Columnable a, ColumnifyRep (KindOf a) a) => Vector a -> Column Source #
toColumn :: (Columnable a, ColumnifyRep (KindOf a) a) => [a] -> Column Source #
columnLength :: Column -> Int Source #
O(1) Gets the number of elements in the column.
columnTypeString :: Column -> String Source #
type Columnable a = (Columnable' a, ColumnifyRep (KindOf a) a, UnboxIf a, SBoolI (Unboxable a)) Source #
toRowValue :: Columnable' a => a -> RowValue Source #
itransform :: (Typeable b, Typeable c, Columnable b, Columnable c) => (Int -> b -> c) -> Column -> Maybe Column Source #
Applies a function that returns an unboxed result to an unboxed vector, storing the result in a column.
ifoldrColumn :: (Columnable a, Columnable b) => (Int -> a -> b -> b) -> b -> Column -> Maybe b Source #
data TypedColumn a where Source #
Constructors
TColumn :: forall a. Columnable a => Column -> TypedColumn a |
Instances
Show a => Show (TypedColumn a) Source # | |
Defined in DataFrame.Internal.Column Methods showsPrec :: Int -> TypedColumn a -> ShowS # show :: TypedColumn a -> String # showList :: [TypedColumn a] -> ShowS # |
transform :: (Columnable b, Columnable c, UnboxIf c, Typeable b, Typeable c) => (b -> c) -> Column -> Maybe Column Source #
Generic column transformation (no index).
unwrapTypedColumn :: TypedColumn a -> Column Source #
getIndices :: Vector Int -> Vector a -> Vector a Source #
data HistogramConfig Source #
readByteStringInt :: HasCallStack => ByteString -> Maybe Int Source #
readDouble :: HasCallStack => Text -> Maybe Double Source #
readIntegerEither :: HasCallStack => Text -> Either Text Integer Source #
readIntEither :: HasCallStack => Text -> Either Text Int Source #
readDoubleEither :: HasCallStack => Text -> Either Text Double Source #
readWithDefault :: (HasCallStack, Read a) => a -> Text -> a Source #
columnVersionString :: Column -> String Source #
type family Unboxable a :: Bool where ... Source #
Equations
Unboxable Int = 'True | |
Unboxable Int8 = 'True | |
Unboxable Int16 = 'True | |
Unboxable Int32 = 'True | |
Unboxable Int64 = 'True | |
Unboxable Word = 'True | |
Unboxable Word8 = 'True | |
Unboxable Word16 = 'True | |
Unboxable Word32 = 'True | |
Unboxable Word64 = 'True | |
Unboxable Char = 'True | |
Unboxable Bool = 'True | |
Unboxable Double = 'True | |
Unboxable Float = 'True | |
Unboxable _1 = 'False |
class ColumnifyRep (r :: Rep) a where Source #
Methods
toColumnRep :: Vector a -> Column Source #
Instances
Columnable a => ColumnifyRep 'RBoxed a Source # | |
Defined in DataFrame.Internal.Column Methods toColumnRep :: Vector a -> Column Source # | |
(Columnable a, Unbox a) => ColumnifyRep 'RUnboxed a Source # | |
Defined in DataFrame.Internal.Column Methods toColumnRep :: Vector a -> Column Source # | |
Columnable a => ColumnifyRep 'RGBoxed (Vector a) Source # | |
Defined in DataFrame.Internal.Column Methods toColumnRep :: Vector (Vector a) -> Column Source # | |
(Columnable a, Unbox a) => ColumnifyRep 'RGUnboxed (Vector a) Source # | |
Defined in DataFrame.Internal.Column Methods toColumnRep :: Vector (Vector a) -> Column Source # | |
Columnable a => ColumnifyRep 'ROptional (Maybe a) Source # | |
Defined in DataFrame.Internal.Column Methods toColumnRep :: Vector (Maybe a) -> Column Source # |
toColumnUnboxed :: (Columnable a, Unbox a) => Vector a -> Column Source #
Converts a an unboxed vector to a column making sure to put the vector into an appropriate column type by reflection on the vector's type parameter.
ifilterColumn :: Columnable a => (Int -> a -> Bool) -> Column -> Maybe Column Source #
Filter column with index.
ifoldlColumn :: (Columnable a, Columnable b) => (b -> Int -> a -> b) -> b -> Column -> Maybe b Source #
reduceColumn :: Columnable a => (a -> b) -> Column -> b Source #
zipWithColumns :: (Columnable a, Columnable b, Columnable c) => (a -> b -> c) -> Column -> Column -> Column Source #
interpret :: forall a b. Columnable a => DataFrame -> Expr a -> TypedColumn a Source #
lit :: Columnable a => a -> Expr a Source #
lift2 :: (Columnable c, Columnable b, Columnable a) => (c -> b -> a) -> Expr c -> Expr b -> Expr a Source #
columnNames :: DataFrame -> [Text] Source #
O(k) Get column names of the DataFrame in order of insertion.
Arguments
:: Columnable a | |
=> Text | Column Name |
-> Vector a | Vector to add to column |
-> DataFrame | DataFrame to add column to |
-> DataFrame |
O(n) Adds a vector to the dataframe.
Arguments
:: (Columnable a, Unbox a) | |
=> Text | Column Name |
-> Vector a | Unboxed vector to add to column |
-> DataFrame | DataFrame to add to column |
-> DataFrame |
O(n) Adds an unboxed vector to the dataframe.
insertColumnWithDefault Source #
Arguments
:: Columnable a | |
=> a | Default Value |
-> Text | Column name |
-> Vector a | Data to add to column |
-> DataFrame | DataFrame to add to column |
-> DataFrame |
O(k) Add a column to the dataframe providing a default. This constructs a new vector and also may convert it to an unboxed vector if necessary. Since columns are usually large the runtime is dominated by the length of the list, k.
columnSize :: Text -> DataFrame -> Maybe Int Source #
O(1) Get the number of elements in a given column.
data ColumnInfo Source #
Constructors
ColumnInfo | |
Fields
|
columnInfo :: DataFrame -> DataFrame Source #
O(n) Returns the number of non-null columns in the dataframe and the type associated with each column.
partiallyParsed :: Column -> Int Source #
fromColumnList :: [Column] -> DataFrame Source #
valueCounts :: Columnable a => Text -> DataFrame -> [(a, Int)] Source #
O (k * n) Counts the occurences of each value in a given column.
data HistogramOrientation Source #
Constructors
VerticalHistogram | |
HorizontalHistogram |
data PlotColumns Source #
Constructors
PlotAll | |
PlotSubset [Text] |
plotHistograms :: HasCallStack => PlotColumns -> HistogramOrientation -> DataFrame -> IO () Source #
plotForColumn :: HasCallStack => Text -> Maybe Column -> HistogramOrientation -> DataFrame -> IO () Source #
plotHistogramsBy :: HasCallStack => Text -> PlotColumns -> HistogramOrientation -> DataFrame -> IO () Source #
plotForColumnBy :: HasCallStack => Text -> Text -> Maybe Column -> Maybe Column -> HistogramOrientation -> DataFrame -> IO () Source #
countOccurrences :: Ord a => Vector a -> [(a, Int)] Source #
plotGivenCounts' :: HasCallStack => Text -> [((String, String), Int)] -> IO () Source #
numericHistogram :: (HasCallStack, Columnable a) => Text -> Vector a -> String Source #
plotVerticalGivenCounts :: HasCallStack => Text -> [(String, Int)] -> IO () Source #
plotGivenCounts :: HasCallStack => Text -> [(String, Int)] -> IO () Source #
smallestPartition :: Ord a => a -> [a] -> a Source #
intPlotRanges :: [Int] Source #
createHistogram :: HistogramConfig -> [Double] -> String Source #
largestPartition :: Ord a => a -> [a] -> a Source #
Sort order taken as a parameter by the sortby function.
Constructors
Ascending | |
Descending |
applyStatistics :: (Vector Double -> Vector Double) -> Text -> DataFrame -> Maybe (Vector Double) Source #
derive :: Columnable a => Text -> Expr a -> DataFrame -> DataFrame Source #
O(k) Apply a function to a combination of columns in a dataframe and
add the result into alias
column.
applyMany :: (Columnable b, Columnable c) => (b -> c) -> [Text] -> DataFrame -> DataFrame Source #
O(k * n) Apply a function to given column names in a dataframe.
Arguments
:: Columnable b | |
=> (Int -> b) | Column name | function to apply |
-> Text | |
-> DataFrame | DataFrame to apply operation to |
-> DataFrame |
O(k) Convenience function that applies to an int column.
Arguments
:: Columnable b | |
=> (Double -> b) | Column name | function to apply |
-> Text | |
-> DataFrame | DataFrame to apply operation to |
-> DataFrame |
O(k) Convenience function that applies to an double column.
applyWhere :: (Columnable a, Columnable b) => (a -> Bool) -> Text -> (b -> b) -> Text -> DataFrame -> DataFrame Source #
O(k * n) Apply a function to a column only if there is another column value that matches the given criterion.
applyWhere "Age" (<20) "Generation" (const "Gen-Z")
Arguments
:: Columnable a | |
=> Int | Index |
-> (a -> a) | function to apply |
-> Text | Column name |
-> DataFrame | DataFrame to apply operation to |
-> DataFrame |
O(k) Apply a function to the column at a given index.
filterBy :: Columnable a => (a -> Bool) -> Text -> DataFrame -> DataFrame Source #
O(k) a version of filter where the predicate comes first.
filterBy even "x" df
filterWhere :: Expr Bool -> DataFrame -> DataFrame Source #
O(k) filters the dataframe with a row predicate. The arguments in the function must appear in the same order as they do in the list.
filterWhere (["x", "y"], func (\x y -> x + y > 5)) df
filterJust :: Text -> DataFrame -> DataFrame Source #
O(k) removes all rows with Nothing
in a given column from the dataframe.
filterJust df
filterAllJust :: DataFrame -> DataFrame Source #
O(n * k) removes all rows with Nothing
from the dataframe.
filterJust df
cube :: (Int, Int) -> DataFrame -> DataFrame Source #
O(k) cuts the dataframe in a cube of size (a, b) where a is the length and b is the width.
cube (10, 5) df
selectIntRange :: (Int, Int) -> DataFrame -> DataFrame Source #
O(n) select columns by index range of column names.
selectRange :: (Text, Text) -> DataFrame -> DataFrame Source #
O(n) select columns by index range of column names.
appendWithFrontMin :: Ord a => a -> [a] -> [a] Source #
hash' :: Columnable a => a -> Double Source #
This hash function returns the hash when given a non numeric type but the value when given a numeric.
groupByAgg :: Aggregation -> [Text] -> DataFrame -> DataFrame Source #
reduceBy :: (Columnable a, Columnable b) => (forall (v :: Type -> Type). Vector v a => v a -> b) -> Text -> DataFrame -> DataFrame Source #
reduceByAgg :: Aggregation -> Text -> DataFrame -> DataFrame Source #
readCsv :: String -> IO DataFrame Source #
Reads a CSV file from the given path. Note this file stores intermediate temporary files while converting the CSV from a row to a columnar format.
readSeparated :: Char -> ReadOptions -> String -> IO DataFrame Source #
Reads a character separated file into a dataframe using mutable vectors.
readTsv :: String -> IO DataFrame Source #
Reads a tab separated file from the given path. Note this file stores intermediate temporary files while converting the CSV from a row to a columnar format.
fillColumns :: Int -> Char -> IOVector Column -> IOVector [(Int, Text)] -> Handle -> IO () Source #
Reads rows from the handle and stores values in mutable vectors.
freezeColumn :: IOVector Column -> Vector [(Int, Text)] -> ReadOptions -> Int -> IO (Maybe Column) Source #
Freezes a mutable vector into an immutable one, trimming it to the actual row count.
inferValueType :: Text -> Text Source #
writeValue :: IOVector Column -> IOVector [(Int, Text)] -> Int -> Int -> Text -> IO () Source #
Writes a value into the appropriate column, resizing the vector if necessary.
quotedField :: Parser Text Source #