[Haskell-beginners] A seemingly simple use-case for Template Haskell

Mario Lang mlang at delysid.org
Thu Sep 29 14:54:13 UTC 2016


Frerich Raabe <raabe at froglogic.com> writes:

> On 2016-09-28 15:06, Mario Lang wrote:
>> In a small project of mine, I have this basically auto-generated data
>> type:
>>
>> -- Braille music code only uses the old 6-dot system.  We enumerate all
>> -- possible dot patterns to use the type system to avoid accidentally
>> -- specifying invalid dot patterns in the source code.
>> --
>> -- gen :: String
>> -- gen =
>> --     "data Braille = " ++ intercalate " | " ctors ++ " deriving
>> (Enum, Eq)" where
>> --   ctors = "NoDots" : map ctorName [1..63] where
>> --     ctorName :: Int -> String
>> --     ctorName = (++) "Dot" . concatMap (show . succ) . flip filter
>> [0..5] . testBit
>>
>> data SixDots = NoDots | Dot1 | Dot2 | Dot12 | Dot3 | Dot13 | Dot23 | Dot123
>>              | Dot4 | Dot14 | Dot24 | Dot124 | Dot34 | Dot134 | Dot234
>>              | Dot1234 | Dot5 | Dot15 | Dot25 | Dot125 | Dot35 | Dot135
>>              | Dot235 | Dot1235 | Dot45 | Dot145 | Dot245 | Dot1245 | Dot345
>>              | Dot1345 | Dot2345 | Dot12345 | Dot6 | Dot16 | Dot26 | Dot126
>>              | Dot36 | Dot136 | Dot236 | Dot1236 | Dot46 | Dot146 | Dot246
>>              | Dot1246 | Dot346 | Dot1346 | Dot2346 | Dot12346 | Dot56 | Dot156
>>              | Dot256 | Dot1256 | Dot356 | Dot1356 | Dot2356 | Dot12356
>>              | Dot456 | Dot1456 | Dot2456 | Dot12456 | Dot3456 | Dot13456
>>              | Dot23456 | Dot123456
>>              deriving (Bounded, Enum, Eq, Read, Show)
>>
>> So, while actually quite simple, this looks like an opportunity to use
>> Template Haskell for me.  In other words, I want to figure out what is
>> necessary to generate this data type with TH, instead of the gen
>> function that basically generates a piece of plain Haskell code.
>
> Here's one way to do it (the 'ctorNames' definition is copied out of
> your comment):
>
> --- Mario.hs ---
> module Mario (makeDotsType) where
>
> import Data.Bits (testBit)
> import Language.Haskell.TH
>
> ctorNames :: [String]
> ctorNames = "NoDots" : map ctorName [1..63]
>   where
>     ctorName :: Int -> String
>     ctorName = (++) "Dot" . concatMap (show . succ) . flip filter
> [0..5] . testBit
>
> makeDotsType :: Q [Dec]
> makeDotsType = do
>     let ctors = map (\n -> NormalC (mkName n) []) ctorNames
>     let instances = map mkName ["Bounded", "Enum", "Eq", "Read", "Show"]
>     return [DataD [] (mkName "SixDots") [] ctors instances]
> ---
>
> --- Main.hs ---
> {-# LANGUAGE TemplateHaskell #-}
>
> import Mario
>
> $(makeDotsType)
> ---
>
> If you compile this with
>
> $ ghc -ddump-splices Main.hs
>
> You can see what type definition that '$(makeDotsType)' expands to.

Oh, thank you!  It could have been so simple...

> For what it's worth, this may not compile with all versions of the TH
> support in GHC; I wrote the above code using GHC 7.10.2.

Works here.

> In general, I find -ddump-splices invaluable when using TH. I use it
> every minute or so to see what code I'm currently generating. What's
> noteworthy is that (as mentioned in the 'Using Template Haskell'
> section of the GHC user guide) that
>
>   You can only run a function at compile time if it is imported from
> another module. That is, you can't define
>   a function in a module, and call it from within a splice in the same
> module.
>
> That's why I used a separate 'Mario' module above.

Yes, I was aware of the need to put the function in a different module.

Thanks again, a working example is really nice to play with.

-- 
CYa,
  ⡍⠁⠗⠊⠕


More information about the Beginners mailing list