Skip to content

Instantly share code, notes, and snippets.

@edwintorok
Last active August 23, 2020 19:49
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save edwintorok/b76b7118490840a6306d17aa64f86c35 to your computer and use it in GitHub Desktop.
Save edwintorok/b76b7118490840a6306d17aa64f86c35 to your computer and use it in GitHub Desktop.
let prologue =
{|
{-# language DeriveGeneric #-}
module Parser where
import Data.Csv
import qualified Data.Vector as V
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import GHC.Generics
import Control.Monad
import Text.Read(readEither)
import Data.Time.Calendar
instance FromField DayOfWeek where
parseField f = case readEither (BS.unpack f) of
Left errMsg -> fail errMsg
Right r -> pure r
|}
let epilogue =
{|
instance ToRecord InputRecord where
instance FromRecord InputRecord where
instance ToField DayOfWeek where
main = do
input <- BSL.readFile "input.csv"
either putStrLn (V.mapM_ (print :: InputRecord -> IO ())) $ decode HasHeader input
|}
let () =
print_endline prologue ;
print_endline {|data InputRecord = InputRecord { |} ;
let inpath = Sys.argv.(1) in
Csv.Rows.load ~has_header:true inpath
|> List.map Csv.Row.to_list
|> List.mapi (fun i -> function
| [field; typ; _parser] ->
let i = i + 2 in
let field = String.lowercase_ascii field in
Printf.sprintf "{-# LINE %d \"%s\" #-}\n" i inpath ^
(if i > 2 then "," else "") ^
Printf.sprintf "%s :: %s" field typ
| line ->
failwith ("Unknown line format: " ^ String.concat "," line))
|> List.iter print_endline ;
print_endline {|} deriving (Generic, Show)|} ;
print_endline epilogue
@edwintorok
Copy link
Author

edwintorok commented Aug 23, 2020

With this dune file:

(executable
 (name codegen)
 (libraries stdio csv)
 )

Generates this output:

dune exec ./codegen.exe ~/code-gen-tutorial/test/input.csv
                     
module Parser where
import Data.Csv
import qualified Data.ByteString.Lazy.Char8 as BS
import GHC.Generics
import Control.Monad

data InputRecord = InputRecord {
{-# LINE "/home/edwin-work/code-gen-tutorial/test/input.csv" 2 #-}
	Name :: String
{-# LINE "/home/edwin-work/code-gen-tutorial/test/input.csv" 3 #-}
	Age :: Int
{-# LINE "/home/edwin-work/code-gen-tutorial/test/input.csv" 4 #-}
	Date :: DayOfWeek
} deriving (Generic, Show)

instance ToRecord InputRecord where
 
main = do
  input <- BS.readFile "input.csv"
  either putStrLn (mapM print) $ decode HasHeader input

@mgajda
Copy link

mgajda commented Aug 23, 2020

Excellent. Now try to compile generated code with GHC, or generate parser in OCaml

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment