Skip to content

Instantly share code, notes, and snippets.

@Lysxia
Created April 3, 2018 13:27
Show Gist options
  • Save Lysxia/8fc397cf55c436e69d2390df1301cea7 to your computer and use it in GitHub Desktop.
Save Lysxia/8fc397cf55c436e69d2390df1301cea7 to your computer and use it in GitHub Desktop.
Parsing CSV records with HKD and generics-sop
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import qualified GHC.Generics as G
import Generics.SOP
import Data.Proxy (Proxy(..))
import Text.Read (readMaybe)
type family s @@ x
type instance Id @@ x = x
type instance Cn a @@ x = a
type instance Tc f @@ x = f x
data Id
data Cn (a :: *)
data Tc (f :: * -> *)
data UserF f = User
{ name :: f @@ String
, age :: f @@ Int
} deriving G.Generic
type User = UserF Id
instance Generic (UserF f)
deriving instance Show User
type FromField = Read
-- Constraint synonym: ParseFrom x y = (x ~ Int, FromField y)
-- but ParseFrom can be partially applied
type ParseFrom' x y = (x ~ Int, FromField y)
class ParseFrom' x y => ParseFrom x y
instance ParseFrom' x y => ParseFrom x y
type Record = [String]
parseRec :: _
=> p (Cn Int) -> Record -> Maybe (p Id)
parseRec ixes r =
fmap to .
hsequence .
htrans (Proxy :: Proxy ParseFrom) (\(I i) -> read (r !! i)) .
from $
ixes
parseUser :: Record -> Maybe User
parseUser = parseRec $ User { name = 0, age = 2 } -- just one number for each field
main = do
print (parseUser ["\"Joe\"", "M", "43"])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment