| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DataFrame.Functions
Synopsis
- name :: Show a => Expr a -> Text
- col :: Columnable a => Text -> Expr a
- as :: Columnable a => Expr a -> Text -> (Text, UExpr)
- ifThenElse :: Columnable a => Expr Bool -> Expr a -> Expr a -> Expr a
- lit :: Columnable a => a -> Expr a
- lift :: (Columnable a, Columnable b) => (a -> b) -> Expr a -> Expr b
- lift2 :: (Columnable c, Columnable b, Columnable a) => (c -> b -> a) -> Expr c -> Expr b -> Expr a
- toDouble :: (Columnable a, Real a) => Expr a -> Expr Double
- div :: (Integral a, Columnable a) => Expr a -> Expr a -> Expr a
- mod :: (Integral a, Columnable a) => Expr a -> Expr a -> Expr a
- (==) :: (Columnable a, Eq a) => Expr a -> Expr a -> Expr Bool
- eq :: (Columnable a, Eq a) => Expr a -> Expr a -> Expr Bool
- (<) :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- lt :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- (>) :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- gt :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr Bool
- (<=) :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- leq :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- (>=) :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- geq :: (Columnable a, Ord a, Eq a) => Expr a -> Expr a -> Expr Bool
- and :: Expr Bool -> Expr Bool -> Expr Bool
- or :: Expr Bool -> Expr Bool -> Expr Bool
- not :: Expr Bool -> Expr Bool
- count :: Columnable a => Expr a -> Expr Int
- mode :: (Columnable a, Eq a) => Expr a -> Expr a
- minimum :: (Columnable a, Ord a) => Expr a -> Expr a
- maximum :: (Columnable a, Ord a) => Expr a -> Expr a
- sum :: (Columnable a, Num a, Unbox a) => Expr a -> Expr a
- mean :: (Columnable a, Real a, Unbox a) => Expr a -> Expr Double
- variance :: (Columnable a, Real a, Unbox a) => Expr a -> Expr Double
- median :: (Columnable a, Real a, Unbox a) => Expr a -> Expr Double
- percentile :: Int -> Expr Double -> Expr Double
- stddev :: (Columnable a, Real a, Unbox a) => Expr a -> Expr Double
- zScore :: Expr Double -> Expr Double
- pow :: (Columnable a, Num a) => Int -> Expr a -> Expr a
- relu :: (Columnable a, Num a) => Expr a -> Expr a
- min :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr a
- max :: (Columnable a, Ord a) => Expr a -> Expr a -> Expr a
- reduce :: (Columnable a, Columnable b) => Expr b -> a -> (a -> b -> a) -> Expr a
- generateConditions :: TypedColumn Double -> [Expr Bool] -> [Expr Double] -> DataFrame -> [Expr Bool]
- generatePrograms :: [Expr Bool] -> [Expr Double] -> [Expr Double] -> [Expr Double] -> [Expr Double]
- isLiteral :: Expr a -> Bool
- deduplicate :: Columnable a => DataFrame -> [Expr a] -> [(Expr a, TypedColumn a)]
- equivalent :: DataFrame -> Expr Double -> Expr Double -> Bool
- synthesizeFeatureExpr :: Text -> BeamConfig -> DataFrame -> Either String (Expr Double)
- f1FromBinary :: Vector Double -> Vector Double -> Maybe Double
- f1FromCounts :: Int -> Int -> Int -> Maybe Double
- fitClassifier :: Text -> Int -> Int -> DataFrame -> Either String (Expr Int)
- percentiles :: DataFrame -> [Expr Double]
- fitRegression :: Text -> Int -> Int -> DataFrame -> Either String (Expr Double)
- data LossFunction
- getLossFunction :: LossFunction -> Vector Double -> Vector Double -> Maybe Double
- data BeamConfig = BeamConfig {}
- defaultBeamConfig :: BeamConfig
- beamSearch :: DataFrame -> BeamConfig -> TypedColumn Double -> [Expr Double] -> [Expr Bool] -> [Expr Double] -> Maybe (Expr Double)
- pickTopN :: DataFrame -> TypedColumn Double -> BeamConfig -> [(Expr Double, TypedColumn a)] -> [Expr Double]
- pickTopNBool :: DataFrame -> TypedColumn Double -> [(Expr Bool, TypedColumn Bool)] -> [Expr Bool]
- satisfiesExamples :: DataFrame -> TypedColumn Double -> Expr Double -> Bool
- isReservedId :: Text -> Bool
- isVarId :: Text -> Bool
- isHaskellIdentifier :: Text -> Bool
- sanitize :: Text -> Text
- typeFromString :: [String] -> Q Type
- declareColumns :: DataFrame -> DecsQ
Documentation
ifThenElse :: Columnable a => Expr Bool -> Expr a -> Expr a -> Expr a Source #
lit :: Columnable a => a -> Expr a Source #
lift :: (Columnable a, Columnable b) => (a -> b) -> Expr a -> Expr b Source #
lift2 :: (Columnable c, Columnable b, Columnable a) => (c -> b -> a) -> Expr c -> Expr b -> Expr a Source #
reduce :: (Columnable a, Columnable b) => Expr b -> a -> (a -> b -> a) -> Expr a Source #
generateConditions :: TypedColumn Double -> [Expr Bool] -> [Expr Double] -> DataFrame -> [Expr Bool] Source #
generatePrograms :: [Expr Bool] -> [Expr Double] -> [Expr Double] -> [Expr Double] -> [Expr Double] Source #
deduplicate :: Columnable a => DataFrame -> [Expr a] -> [(Expr a, TypedColumn a)] Source #
equivalent :: DataFrame -> Expr Double -> Expr Double -> Bool Source #
Checks if two programs generate the same outputs given all the same inputs.
data LossFunction Source #
Constructors
| PearsonCorrelation | |
| MutualInformation | |
| MeanSquaredError | |
| F1 |
getLossFunction :: LossFunction -> Vector Double -> Vector Double -> Maybe Double Source #
data BeamConfig Source #
Constructors
| BeamConfig | |
Fields
| |
pickTopN :: DataFrame -> TypedColumn Double -> BeamConfig -> [(Expr Double, TypedColumn a)] -> [Expr Double] Source #
pickTopNBool :: DataFrame -> TypedColumn Double -> [(Expr Bool, TypedColumn Bool)] -> [Expr Bool] Source #
satisfiesExamples :: DataFrame -> TypedColumn Double -> Expr Double -> Bool Source #
isReservedId :: Text -> Bool Source #
isHaskellIdentifier :: Text -> Bool Source #
declareColumns :: DataFrame -> DecsQ Source #