Skip to content

Instantly share code, notes, and snippets.

@kfish
Created November 15, 2012 02:49
Show Gist options
  • Save kfish/4076344 to your computer and use it in GitHub Desktop.
Save kfish/4076344 to your computer and use it in GitHub Desktop.
Data constructor field names as [String] using Template Haskell
{-# LANGUAGE TemplateHaskell #-}
module FieldNames (
fieldNames
) where
import Data.List (nub)
import Language.Haskell.TH
-- | Generate a list of all field names used in the constructors
-- of the input type.
--
-- /e.g./
--
-- @
-- data Foo = FooF { fooX :: Int, fooY :: 'Float' }
-- | FooD { fooX :: Int, fooZ :: 'Double' }
-- 'fieldNames' ''Foo
-- @
--
-- will create
--
-- @
-- ["fooX", "fooY", "fooZ"]
-- @
--
fieldNames :: Name -> ExpQ
fieldNames t = do
TyConI (DataD _ _ _ constructors _) <- reify t
let ns = nub (concatMap names constructors)
l <- [| ns |]
return l
where
names :: Con -> [String]
names (RecC _ fields) = map (nameBase . fst3) fields
names (ForallC _ _ con) = names con
names _ = []
fst3 (x,_,_) = x
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import FieldNames
data Foo = FooF { fooX :: Int, fooY :: Float }
| FooD { fooX :: Int, fooZ :: Double }
data D = D {
dInt :: Int
, dDouble :: Double
, dString :: String
}
data F = forall a . F {
fList :: [a]
, fMaybe :: Maybe a
}
main :: IO ()
main = do
print $(fieldNames ''Foo)
print $(fieldNames ''D)
print $(fieldNames ''F)
@v0d1ch
Copy link

v0d1ch commented Jun 12, 2018

This is great, only thing is that this https://gist.github.com/kfish/4076344#file-fieldnames-hs-L29 line needs another param , guess that the api changed a bit

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