Frames-0.7.0: Data frames For working with tabular data files

Safe HaskellNone
LanguageHaskell2010

Frames.TH

Contents

Description

Code generation of types relevant to Frames use-cases. Generation may be driven by an automated inference process or manual use of the individual helpers.

Synopsis

Documentation

recDec :: [Type] -> Type Source #

Generate a column type.

mkColSynDec :: TypeQ -> Name -> DecQ Source #

Declare a type synonym for a column.

mkColLensDec :: Name -> Type -> Text -> DecsQ Source #

Declare lenses for working with a column.

colDec :: Text -> String -> Text -> Either (String -> Q [Dec]) Type -> Q (Type, [Dec]) Source #

For each column, we declare a type synonym for its type, and a Proxy value of that type.

declareColumn :: Text -> Name -> DecsQ Source #

Splice for manually declaring a column of a given type. For example, declareColumn "x2" ''Double will declare a type synonym type X2 = "x2" :-> Double and a lens x2.

declarePrefixedColumn :: Text -> Text -> Name -> DecsQ Source #

Splice for manually declaring a column of a given type in which the generated type synonym's name has a prefix applied to the column name. For example, declarePrefixedColumn "x2" "my" ''Double will declare a type synonym type MyX2 = "x2" :-> Double and a lens myX2.

Default CSV Parsing

data RowGen (a :: [Type]) Source #

Control how row and named column types are generated. The type argument is a type-level list of the possible column types.

Constructors

RowGen 

Fields

rowGen :: FilePath -> RowGen CommonColumns Source #

A default RowGen. This instructs the type inference engine to get column names from the data file, use the default column separator (a comma), infer column types from the default Columns set of types, and produce a row type with name Row.

rowGenCat :: FilePath -> RowGen CommonColumnsCat Source #

Like rowGen, but will also generate custom data types for Categorical variables with up to 8 distinct variants.

tableTypes :: String -> FilePath -> DecsQ Source #

Like tableType, but additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens @Foo, and foo' = rlens' @Foo.

Customized Data Set Parsing

prefixSize :: Int Source #

Inspect no more than this many lines when inferring column types.

colNamesP :: Monad m => Producer [Text] m () -> m [Text] Source #

Generate a type for a row of a table. This will be something like Record ["x" :-> a, "y" :-> b, "z" :-> c]. Column type synonyms are not generated (see tableTypes'). tableType' :: forall a. (ColumnTypeable a, Monoid a) => RowGen a -> DecsQ tableType' (RowGen {..}) = pure . TySynD (mkName rowTypeName) [] $ (runIO (P.runSafeT (readColHeaders opts lineSource)) >>= recDec') where recDec' = recDec . map (second colType) :: [(T.Text, a)] -> Q Type colNames' | null columnNames = Nothing | otherwise = Just (map T.pack columnNames) opts = ParserOptions colNames' separator (RFC4180Quoting '"') lineSource = lineReader separator >-> P.take prefixSize

Tokenize the first line of a ’P.Producer’.

tableTypesText' :: forall a c. (c ~ CoRec ColInfo a, ColumnTypeable c, Monoid c) => RowGen a -> DecsQ Source #

Generate a type for a row of a table all of whose columns remain unparsed Text values.

tableTypes' :: forall a c. (c ~ CoRec ColInfo a, ColumnTypeable c, Monoid c) => RowGen a -> DecsQ Source #

Generate a type for a row of a table. This will be something like Record ["x" :-> a, "y" :-> b, "z" :-> c]. Additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens @Foo, and foo' = rlens' @Foo.