
Mark Fredrickson
Hello,
I writing a program that operates on some static data, currently saved in CSV files. Right now I parse the files at run time and then generate hashmap tables to connect the different data.
Since I'm only ever operating on static data, I'm wondering if I can generate module files that capture the records as a sum type. To access the fields of the records, I could then imagine functions that exhaustively map the constructors to the data.
Do any tools to generate .hs files from CSV or other formats exist? Insofar as this question has been asked before, the recommendation is "use Template Haskell", which makes sense, but is a less complete solution than I'm hoping for.
How does the TH hack below look? See this Gist for this code and a test-case. Unfortunately there are a few gotchas here, 1. The record type needs a `Lift` instance[2]. There are a pain to write but can be derived[3] 2. The type of your data can't be defined in the same module as the TH splice due to GHC's stage restriction Cheers, - Ben [1] https://gist.github.com/bgamari/efad8560ab7dd38e9407 [2] http://hackage.haskell.org/package/template-haskell-2.9.0.0/docs/Language-Ha... [3] http://hackage.haskell.org/package/th-lift {-# LANGUAGE TemplateHaskell, FlexibleContexts #-} module StaticCSV (staticCSV) where import Control.Applicative import Data.Csv as Csv hiding (Name) import Data.Proxy import Data.Data import Language.Haskell.TH import Language.Haskell.TH.Syntax (Lift, lift) import qualified Data.ByteString.Lazy as BSL import qualified Data.Vector as V staticCSV :: (FromRecord a, Lift (V.Vector a)) => FilePath -> Proxy a -> ExpQ staticCSV fileName ty = do contents <- runIO $ BSL.readFile fileName csv <- case decode NoHeader contents of Right a -> return $ fmap (flip asProxyTypeOf ty) a Left err -> fail err [| csv |] instance Lift a => Lift (V.Vector a) where lift v = do list <- ListE <$> mapM lift (V.toList v) return $ AppE (VarE 'V.fromList) list