Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.DataFrame
Synopsis
- data Function where
- F1 :: forall a b. (Columnable a, Columnable b) => (a -> b) -> Function
- F2 :: forall a b c. (Columnable a, Columnable b, Columnable c) => (a -> b -> c) -> Function
- F3 :: forall a b c d. (Columnable a, Columnable b, Columnable c, Columnable d) => (a -> b -> c -> d) -> Function
- F4 :: forall a b c d e. (Columnable a, Columnable b, Columnable c, Columnable d, Columnable e) => (a -> b -> c -> d -> e) -> Function
- Cond :: forall a. Columnable a => (a -> Bool) -> Function
- ICond :: forall a. Columnable a => (Int -> a -> Bool) -> Function
- data Column where
- BoxedColumn :: Columnable a => Vector a -> Column
- UnboxedColumn :: (Columnable a, Unbox a) => Vector a -> Column
- OptionalColumn :: Columnable a => Vector (Maybe a) -> Column
- GroupedBoxedColumn :: Columnable a => Vector (Vector a) -> Column
- GroupedUnboxedColumn :: (Columnable a, Unbox a) => Vector (Vector a) -> Column
- GroupedOptionalColumn :: Columnable a => Vector (Vector (Maybe a)) -> Column
- MutableBoxedColumn :: Columnable a => IOVector a -> Column
- MutableUnboxedColumn :: (Columnable a, Unbox a) => IOVector a -> Column
- data DataFrame = DataFrame (Vector (Maybe Column)) (Map Text Int) [Int] (Int, Int)
- type Row = Vector RowValue
- data Aggregation
- 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
- type Columnable a = (Typeable a, Show a, Ord a, Eq a)
- data RowValue where
- Value :: Columnable a => a -> RowValue
- class Transformable a where
- transform :: forall b c. (Columnable b, Columnable c) => (b -> c) -> a -> Maybe a
- data TypeRepList (xs :: [Type]) where
- Nil :: TypeRepList '[]
- Cons :: Typeable x => TypeRep x -> TypeRepList xs -> TypeRepList (x ': xs)
- class WrapFunction a where
- wrapFunction :: a -> Function
- class Columnable a => Columnify a where
- class Columnable a => ColumnifyList a where
- data ColumnInfo = ColumnInfo {
- nameOfColumn :: !Text
- nonNullValues :: !Int
- nullValues :: !Int
- partiallyParsedValues :: !Int
- uniqueValues :: !Int
- typeOfColumn :: !Text
- data HistogramOrientation
- data PlotColumns
- = PlotAll
- | PlotSubset [Text]
- data HistogramConfig = HistogramConfig {}
- data SortOrder
- data ReadOptions = ReadOptions {}
- pattern Empty :: Vector a
- pattern (:<|) :: a -> Vector a -> Vector a
- fromList :: [(Text, Column)] -> DataFrame
- apply :: forall b c. (Columnable b, Columnable c) => (b -> c) -> Text -> DataFrame -> DataFrame
- empty :: DataFrame
- null :: DataFrame -> Bool
- filter :: forall a. Columnable a => Text -> (a -> Bool) -> DataFrame -> DataFrame
- defaultOptions :: ReadOptions
- range :: (Int, Int) -> DataFrame -> DataFrame
- take :: Int -> DataFrame -> DataFrame
- sortBy :: SortOrder -> [Text] -> DataFrame -> DataFrame
- groupBy :: [Text] -> DataFrame -> DataFrame
- uncons :: Vector a -> Maybe (a, Vector a)
- sum :: Text -> DataFrame -> Maybe Double
- drop :: Int -> DataFrame -> DataFrame
- rotate :: [String] -> [String]
- readInt :: HasCallStack => Text -> Maybe Int
- fold :: (a -> DataFrame -> DataFrame) -> [a] -> DataFrame -> DataFrame
- readInteger :: HasCallStack => Text -> Maybe Integer
- select :: [Text] -> DataFrame -> DataFrame
- median :: Text -> DataFrame -> Maybe Double
- variance :: Text -> DataFrame -> Maybe Double
- mean :: Text -> DataFrame -> Maybe Double
- skewness :: Text -> DataFrame -> Maybe Double
- correlation :: Text -> Text -> DataFrame -> Maybe Double
- formatNumber :: Double -> String
- clip :: Int -> Int -> Int -> Int
- rename :: Text -> Text -> DataFrame -> DataFrame
- selectBy :: (Text -> Bool) -> DataFrame -> DataFrame
- mkRowRep :: DataFrame -> Set Text -> Int -> Int
- isNullish :: Text -> Bool
- columnLength :: Column -> Int
- columnTypeString :: Column -> String
- expandColumn :: Int -> Column -> Column
- getColumn :: Text -> DataFrame -> Maybe Column
- dimensions :: DataFrame -> (Int, Int)
- mkRowFromArgs :: [Text] -> DataFrame -> Int -> Row
- toRowValue :: forall a. Columnable a => a -> RowValue
- frequencies :: Text -> DataFrame -> DataFrame
- itransform :: forall b c. (Columnable b, Columnable c) => (Int -> b -> c) -> Column -> Maybe Column
- ifoldrColumn :: forall a b. (Columnable a, Columnable b) => (Int -> a -> b -> b) -> b -> Column -> Maybe b
- funcApply :: forall c. Columnable c => Vector RowValue -> Function -> c
- 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)
- func :: forall fn. WrapFunction fn => fn -> Function
- 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
- unboxableTypes :: TypeRepList '[Int, Int8, Int16, Int32, Int64, Word, Word8, Word16, Word32, Word64, Char, Double, Float, Bool]
- numericTypes :: TypeRepList '[Int, Int8, Int16, Int32, Int64, Double, Float]
- matchesAnyType :: forall a xs. Typeable a => TypeRepList xs -> TypeRep a -> Bool
- testUnboxable :: forall a. Typeable a => TypeRep a -> Bool
- testNumeric :: forall a. Typeable a => TypeRep a -> Bool
- isGrouped :: Column -> Bool
- columnVersionString :: Column -> String
- toColumnUnboxed :: forall a. (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
- transformUnboxed :: forall a b. (Columnable a, Unbox a, Columnable b) => (a -> b) -> Vector a -> Column
- itransformUnboxed :: forall a b. (Columnable a, Unbox a, Columnable b) => (Int -> a -> b) -> Vector a -> Column
- ifilterColumn :: forall a. Columnable a => (Int -> a -> Bool) -> Column -> Maybe Column
- ifilterColumnF :: Function -> Column -> Maybe Column
- ifoldlColumn :: forall a b. (Columnable a, Columnable b) => (b -> Int -> a -> b) -> b -> Column -> Maybe b
- reduceColumn :: forall a b. Columnable a => (a -> b) -> Column -> b
- safeReduceColumn :: forall a b. Typeable a => (a -> b) -> Column -> Maybe b
- zipColumns :: Column -> Column -> Column
- nulls :: Column -> Int
- asText :: DataFrame -> Text
- initialColumnSize :: Int
- metadata :: DataFrame -> String
- toRowList :: [Text] -> DataFrame -> [Row]
- toRowVector :: [Text] -> DataFrame -> Vector Row
- sortedIndexes' :: Bool -> Vector Row -> Vector Int
- columnNames :: DataFrame -> [Text]
- insertColumn :: forall a. Columnable a => Text -> Vector a -> DataFrame -> DataFrame
- insertColumn' :: Text -> Maybe Column -> DataFrame -> DataFrame
- cloneColumn :: Text -> Text -> DataFrame -> DataFrame
- insertUnboxedColumn :: forall a. (Columnable a, Unbox a) => Text -> Vector a -> DataFrame -> DataFrame
- insertColumnWithDefault :: forall a. Columnable a => a -> Text -> Vector a -> DataFrame -> DataFrame
- columnSize :: Text -> DataFrame -> Maybe Int
- columnInfo :: DataFrame -> DataFrame
- partiallyParsed :: Column -> Int
- valueCounts :: forall a. Columnable a => Text -> DataFrame -> [(a, Int)]
- 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 :: forall a. (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)]
- 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
- deriveFrom :: ([Text], Function) -> Text -> DataFrame -> DataFrame
- derive :: forall b c. (Columnable b, Columnable c) => Text -> (b -> c) -> Text -> 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 :: forall a b. (Columnable a, Columnable b) => (a -> Bool) -> Text -> (b -> b) -> Text -> DataFrame -> DataFrame
- applyAtIndex :: forall a. Columnable a => Int -> (a -> a) -> Text -> DataFrame -> DataFrame
- takeLast :: Int -> DataFrame -> DataFrame
- dropLast :: Int -> DataFrame -> DataFrame
- filterBy :: Columnable a => (a -> Bool) -> Text -> DataFrame -> DataFrame
- filterWhere :: ([Text], Function) -> DataFrame -> DataFrame
- filterJust :: Text -> 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 :: forall a b. (Columnable a, Columnable b) => (forall v. Vector v a => v a -> b) -> Text -> DataFrame -> DataFrame
- reduceByAgg :: Aggregation -> Text -> DataFrame -> DataFrame
- aggregate :: [(Text, Aggregation)] -> DataFrame -> DataFrame
- 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
Constructors
F1 :: forall a b. (Columnable a, Columnable b) => (a -> b) -> Function | |
F2 :: forall a b c. (Columnable a, Columnable b, Columnable c) => (a -> b -> c) -> Function | |
F3 :: forall a b c d. (Columnable a, Columnable b, Columnable c, Columnable d) => (a -> b -> c -> d) -> Function | |
F4 :: forall a b c d e. (Columnable a, Columnable b, Columnable c, Columnable d, Columnable e) => (a -> b -> c -> d -> e) -> Function | |
Cond :: forall a. Columnable a => (a -> Bool) -> Function | |
ICond :: forall a. Columnable a => (Int -> a -> Bool) -> Function |
Our representation of a column is a GADT that can store data in either a vector with boxed elements or
Constructors
BoxedColumn :: Columnable a => Vector a -> Column | |
UnboxedColumn :: (Columnable a, Unbox a) => Vector a -> Column | |
OptionalColumn :: Columnable a => Vector (Maybe a) -> Column | |
GroupedBoxedColumn :: Columnable a => Vector (Vector a) -> Column | |
GroupedUnboxedColumn :: (Columnable a, Unbox a) => Vector (Vector a) -> Column | |
GroupedOptionalColumn :: Columnable a => Vector (Vector (Maybe a)) -> Column | |
MutableBoxedColumn :: Columnable a => IOVector a -> Column | |
MutableUnboxedColumn :: (Columnable a, Unbox a) => IOVector a -> Column |
data Aggregation Source #
Instances
Show Aggregation Source # | |
Defined in Data.DataFrame.Operations.Aggregation Methods showsPrec :: Int -> Aggregation -> ShowS # show :: Aggregation -> String # showList :: [Aggregation] -> ShowS # | |
Eq Aggregation Source # | |
Defined in Data.DataFrame.Operations.Aggregation |
data DataFrameException where Source #
Constructors
TypeMismatchException | |
TypeMismatchException' | |
ColumnNotFoundException :: Text -> Text -> [Text] -> DataFrameException |
Instances
Exception DataFrameException Source # | |
Defined in Data.DataFrame.Errors Methods toException :: DataFrameException -> SomeException # fromException :: SomeException -> Maybe DataFrameException # | |
Show DataFrameException Source # | |
Defined in Data.DataFrame.Errors Methods showsPrec :: Int -> DataFrameException -> ShowS # show :: DataFrameException -> String # showList :: [DataFrameException] -> ShowS # |
Constructors
Value :: Columnable a => a -> RowValue |
class Transformable a where Source #
Essentially a "functor" instance of our type-erased Column.
Methods
transform :: forall b c. (Columnable b, Columnable c) => (b -> c) -> a -> Maybe a Source #
Instances
Transformable Column Source # | |
Defined in Data.DataFrame.Internal.Column Methods transform :: (Columnable b, Columnable c) => (b -> c) -> Column -> Maybe Column Source # |
data TypeRepList (xs :: [Type]) where Source #
Constructors
Nil :: TypeRepList '[] | |
Cons :: Typeable x => TypeRep x -> TypeRepList xs -> TypeRepList (x ': xs) |
class WrapFunction a where Source #
Methods
wrapFunction :: a -> Function Source #
Instances
(Columnable a, Columnable b, Columnable c, Columnable d, Columnable e) => WrapFunction (a -> b -> c -> d -> e) Source # | |
Defined in Data.DataFrame.Internal.Function Methods wrapFunction :: (a -> b -> c -> d -> e) -> Function Source # | |
(Columnable a, Columnable b, Columnable c, Columnable d) => WrapFunction (a -> b -> c -> d) Source # | |
Defined in Data.DataFrame.Internal.Function Methods wrapFunction :: (a -> b -> c -> d) -> Function Source # | |
(Columnable a, Columnable b, Columnable c) => WrapFunction (a -> b -> c) Source # | |
Defined in Data.DataFrame.Internal.Function Methods wrapFunction :: (a -> b -> c) -> Function Source # | |
(Columnable a, Columnable b) => WrapFunction (a -> b) Source # | |
Defined in Data.DataFrame.Internal.Function Methods wrapFunction :: (a -> b) -> Function Source # |
class Columnable a => Columnify a where Source #
Methods
toColumn' :: Vector a -> Column Source #
Converts a boxed vector to a column making sure to put the vector into an appropriate column type by reflection on the vector's type parameter.
Instances
Columnable a => Columnify a Source # | |
Defined in Data.DataFrame.Internal.Column | |
Columnable a => Columnify (Vector a) Source # | |
Defined in Data.DataFrame.Internal.Column | |
(Columnable a, Unbox a) => Columnify (Vector a) Source # | |
Columnable a => Columnify (Maybe a) Source # | |
class Columnable a => ColumnifyList a where Source #
Methods
toColumn :: [a] -> Column Source #
Converts a boxed vector to a column making sure to put the vector into an appropriate column type by reflection on the vector's type parameter.
Instances
Columnable a => ColumnifyList a Source # | |
Defined in Data.DataFrame.Internal.Column | |
Columnable a => ColumnifyList (Maybe a) Source # | |
data ColumnInfo Source #
Constructors
ColumnInfo | |
Fields
|
data HistogramOrientation Source #
Constructors
VerticalHistogram | |
HorizontalHistogram |
data PlotColumns Source #
Constructors
PlotAll | |
PlotSubset [Text] |
data HistogramConfig Source #
Sort order taken as a parameter by the sortby function.
Constructors
Ascending | |
Descending |
Arguments
:: forall b c. (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.
Arguments
:: forall a. 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.
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).
sortBy :: SortOrder -> [Text] -> DataFrame -> DataFrame Source #
O(k log n) Sorts the dataframe by a given row.
sortBy "Age" df
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.
readInteger :: HasCallStack => Text -> Maybe Integer Source #
select :: [Text] -> DataFrame -> DataFrame Source #
O(n) Selects a number of columns in a given dataframe.
select ["name", "age"] df
formatNumber :: Double -> String Source #
selectBy :: (Text -> Bool) -> DataFrame -> DataFrame Source #
O(n) select columns by column predicate name.
columnLength :: Column -> Int Source #
O(1) Gets the number of elements in the column.
columnTypeString :: Column -> String Source #
toRowValue :: forall a. Columnable a => a -> RowValue Source #
itransform :: forall b c. (Columnable b, Columnable c) => (Int -> b -> c) -> Column -> Maybe Column Source #
tranform with index.
ifoldrColumn :: forall a b. (Columnable a, Columnable b) => (Int -> a -> b -> b) -> b -> Column -> Maybe b Source #
getIndices :: Vector Int -> Vector a -> Vector a Source #
func :: forall fn. WrapFunction fn => fn -> Function 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 #
unboxableTypes :: TypeRepList '[Int, Int8, Int16, Int32, Int64, Word, Word8, Word16, Word32, Word64, Char, Double, Float, Bool] Source #
matchesAnyType :: forall a xs. Typeable a => TypeRepList xs -> TypeRep a -> Bool Source #
columnVersionString :: Column -> String Source #
toColumnUnboxed :: forall a. (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.
transformUnboxed :: forall a b. (Columnable a, Unbox a, Columnable b) => (a -> b) -> Vector a -> Column Source #
Applies a function that returns an unboxed result to an unboxed vector, storing the result in a column.
itransformUnboxed :: forall a b. (Columnable a, Unbox a, Columnable b) => (Int -> a -> b) -> Vector a -> Column Source #
ifilterColumn :: forall a. Columnable a => (Int -> a -> Bool) -> Column -> Maybe Column Source #
Filter column with index.
ifoldlColumn :: forall a b. (Columnable a, Columnable b) => (b -> Int -> a -> b) -> b -> Column -> Maybe b Source #
reduceColumn :: forall a b. Columnable a => (a -> b) -> Column -> b Source #
columnNames :: DataFrame -> [Text] Source #
O(k) Get column names of the DataFrame in order of insertion.
Arguments
:: forall a. 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
:: forall a. (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
:: forall a. 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.
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 #
valueCounts :: forall a. Columnable a => Text -> DataFrame -> [(a, Int)] Source #
O (k * n) Counts the occurences of each value in a given column.
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 :: forall a. (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 #
applyStatistics :: (Vector Double -> Vector Double) -> Text -> DataFrame -> Maybe (Vector Double) Source #
deriveFrom :: ([Text], Function) -> Text -> DataFrame -> DataFrame Source #
O(k) Apply a function to a combination of columns in a dataframe and
add the result into alias
column.
Arguments
:: forall b c. (Columnable b, Columnable c) | |
=> Text | New name |
-> (b -> c) | function to apply |
-> Text | Derivative column name |
-> DataFrame | DataFrame to apply operation to |
-> DataFrame |
O(k) Apply a function to a given column 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 :: forall a b. (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
:: forall a. 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.
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 :: forall a b. (Columnable a, Columnable b) => (forall v. 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 #