[Haskell-cafe] Automatically generate sum type members -> [String]

Adam Bergmark adam at bergmark.nl
Tue May 19 00:19:51 UTC 2015


Using GHC Generics:
http://hackage.haskell.org/package/generic-deriving-1.7.0/docs/Generics-Deriving-ConNames.html


On Tue, May 19, 2015 at 1:29 AM, Tikhon Jelvis <tikhon at jelv.is> wrote:

> You can get this information through the Data.Data module. There are two
> typeclasses which can be (have to be, I believe) derived for your data
> type, Data and Typeable. The Data class lets you access a representation of
> your type including type constructors.
>
> To set this up, you need to import Data.Data and enable the
> DeriveDataTypeable extension:
>
>     {-# LANGUAGE DeriveDataTypeable #-}
>     import Data.Data
>
>     data Codes = A0100A | A0500A deriving (Show, Data, Typeable)
>
> Now you can get a representation of the type:
>
>     λ> dataTypeOf (undefined :: Codes)
>     DataType {tycon = "Main.Codes", datarep = AlgRep [A0100A,A0500A]}
>
> Since your type is an algebraic data type (AlgRep), the DataRep contains
> its constructors, which you can inspect with functions from the Data.Data
> module.
>
> On Mon, May 18, 2015 at 4:20 PM, Cody Goodman <
> codygman.consulting at gmail.com> wrote:
>
>> Can I use either template Haskell, GHC Generics, or something else to
>> get the list of Constructors in Codes? Then I could do `map show
>> codeSumTypeMembers` and get `["A0100A","A0500A"]`?
>>
>> Here's an example of solving this problem manually:
>>
>> data Codes = A0100A | A0500A deriving Show
>>
>> codeExists "A0100A" = True
>> codeExists "A0500A" = True
>> codeExists _ = False
>>
>>
>> main = print $ codeExists xmlElementName
>>        where xmlElementName = "A0500A"
>>
>> -- λ> main
>> -- True
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150519/ca227f2b/attachment.html>


More information about the Haskell-Cafe mailing list