A seemingly simple use-case for Template Haskell

Hi. As a long-term Lisp fan, and someone who always admired compile-time code-generation, I wanted to at least do something simple with Template Haskell once. 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. I have been reading "A practical Template Haskell Tutorial"[1] but I find it a little bit too terse to actually solve this very little riddle on my own. For one, I find it confusing that some TH functions return "Q Dec" while others just return Dec. I am aware that this is some sort of Monad for the TH system, but I have never seen it explained anywhere. Also, all the examples I can find seem to be mostly focused in generating Q Exp or similar, but I didn't really find an example for Q Dec. I realize this should be simple to figure out on my own, but it apparently is not. I have tried to wrap my head around this on my own at least three times now, but always stopped after an hour or two due to frustration. Is there some comprehensive TH documentation I haven't seen yet? Could you please give me enough of a head-start that I actually manage to write something which can generate this simple data type above? [1] https://wiki.haskell.org/A_practical_Template_Haskell_Tutorial -- CYa, ⡍⠁⠗⠊⠕

Why not just use a datastructure with 6 Bools? E.g.:
data SixDots = SixDots
{ dot1 :: Bool
, dot2 :: Bool
, dot3 :: Bool
, dot4 :: Bool
, dot5 :: Bool
, dot6 :: Bool
}
There may be even better ways to do this, but I would consider something
like this if I were working on this problem.
Although I do end up using TH sometimes, I usually find that it is better
to use non-meta-level solutions when practical.
Best,
Ryan
On Wed, Sep 28, 2016 at 9:06 AM, Mario Lang
Hi.
As a long-term Lisp fan, and someone who always admired compile-time code-generation, I wanted to at least do something simple with Template Haskell once.
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.
I have been reading "A practical Template Haskell Tutorial"[1] but I find it a little bit too terse to actually solve this very little riddle on my own.
For one, I find it confusing that some TH functions return "Q Dec" while others just return Dec. I am aware that this is some sort of Monad for the TH system, but I have never seen it explained anywhere.
Also, all the examples I can find seem to be mostly focused in generating Q Exp or similar, but I didn't really find an example for Q Dec.
I realize this should be simple to figure out on my own, but it apparently is not. I have tried to wrap my head around this on my own at least three times now, but always stopped after an hour or two due to frustration. Is there some comprehensive TH documentation I haven't seen yet? Could you please give me enough of a head-start that I actually manage to write something which can generate this simple data type above?
[1] https://wiki.haskell.org/A_practical_Template_Haskell_Tutorial -- CYa, ⡍⠁⠗⠊⠕ _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Ryan Trinkle
Why not just use a datastructure with 6 Bools? E.g.:
data SixDots = SixDots { dot1 :: Bool , dot2 :: Bool , dot3 :: Bool , dot4 :: Bool , dot5 :: Bool , dot6 :: Bool }
Because it is convenient to have an Enum instance, and because braille dot patterns are used as sort of constants in the code. So if I had a data structure like you described above, I'd still need 64 functions with convenient names that return such a data structure with the appropriate bits set. -- eeek! dot123 :: SixDots' dot123 = SixDots' True True True False False False It seems *a lot* easier to just use a sum type and enumerate all the possibilities. Besides, it seems overly inefficient to use 6 Bools for something that actually just needs 6 bits. Also, the resulting enumeration actually matches the Unicode standard. To illustrate, I have a function to convert Braille dot patterns to Char: toChar :: SixDots -> Char toChar = toEnum . (+ 0x2800) . fromEnum That said, I am not really looking for advice on the example at hand, I am more interested in using that example as a motivation to learn TH. [...]
On Wed, Sep 28, 2016 at 9:06 AM, Mario Lang
wrote: Hi.
As a long-term Lisp fan, and someone who always admired compile-time code-generation, I wanted to at least do something simple with Template Haskell once.
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.
I have been reading "A practical Template Haskell Tutorial"[1] but I find it a little bit too terse to actually solve this very little riddle on my own.
For one, I find it confusing that some TH functions return "Q Dec" while others just return Dec. I am aware that this is some sort of Monad for the TH system, but I have never seen it explained anywhere.
Also, all the examples I can find seem to be mostly focused in generating Q Exp or similar, but I didn't really find an example for Q Dec.
I realize this should be simple to figure out on my own, but it apparently is not. I have tried to wrap my head around this on my own at least three times now, but always stopped after an hour or two due to frustration. Is there some comprehensive TH documentation I haven't seen yet? Could you please give me enough of a head-start that I actually manage to write something which can generate this simple data type above?
[1] https://wiki.haskell.org/A_practical_Template_Haskell_Tutorial
-- CYa, ⡍⠁⠗⠊⠕

Hi Mario, I had a similar itch to scratch when I first started noodling with Haskell, coming from Lisp, and wrote the following for generating enums from a convenient notation: https://github.com/yesodweb/yesod/wiki/Create-String-Based-Enums-With-Templa... https://github.com/yesodweb/yesod/wiki/Create-String-Based-Enums-With-Templa... It’s approaching four years old, so likely no longer works as is, but I hope it is helpful. Even more than with Lisp macros, TH should be seen as a last resort. However, sometimes you gotta scratch. I was frustrated at the time that I couldn’t find any decent examples, and I specifically wanted to learn some TH - regardless of whether there was a better way available. In that wiki page you’ll find code for a custom quasi quoter, and code for generating declarations. I mostly just relied on the template haskell docs: https://hackage.haskell.org/package/template-haskell https://hackage.haskell.org/package/template-haskell which I found to have everything I needed, though of course there is a lot to digest in there. After gaining some familiarity, the types and functions for creating those types feel a natural match to regular Haskell source, and Q is used because otherwise your declarations would be just side effect free values, unable to affect your program. For your needs, find “data Dec” in the template haskell docs, and you’ll see that `DataD` matches what you need at term level. Then take a look at `dataD`, a function that will construct your declaration, using Q. Cheers, Si
On 28 Sep 2016, at 15:06, Mario Lang
wrote: Hi.
As a long-term Lisp fan, and someone who always admired compile-time code-generation, I wanted to at least do something simple with Template Haskell once.
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.
I have been reading "A practical Template Haskell Tutorial"[1] but I find it a little bit too terse to actually solve this very little riddle on my own.
For one, I find it confusing that some TH functions return "Q Dec" while others just return Dec. I am aware that this is some sort of Monad for the TH system, but I have never seen it explained anywhere.
Also, all the examples I can find seem to be mostly focused in generating Q Exp or similar, but I didn't really find an example for Q Dec.
I realize this should be simple to figure out on my own, but it apparently is not. I have tried to wrap my head around this on my own at least three times now, but always stopped after an hour or two due to frustration. Is there some comprehensive TH documentation I haven't seen yet? Could you please give me enough of a head-start that I actually manage to write something which can generate this simple data type above?
[1] https://wiki.haskell.org/A_practical_Template_Haskell_Tutorial -- CYa, ⡍⠁⠗⠊⠕ _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

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. 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. 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.
Also, all the examples I can find seem to be mostly focused in generating Q Exp or similar, but I didn't really find an example for Q Dec.
I uploaded a couple of my own exercises for using TH on GitHub: https://github.com/frerich/random-derive https://github.com/frerich/catamorphism https://github.com/frerich/smartconstructor All of them deal with generating a 'Dec' at https://hackage.haskell.org/package/template-haskell-2.11.0.0/docs/Language-... ...and then work my way down. Hope that helps! -- Frerich Raabe - raabe@froglogic.com www.froglogic.com - Multi-Platform GUI Testing

Frerich Raabe
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, ⡍⠁⠗⠊⠕
participants (4)
-
Frerich Raabe
-
Mario Lang
-
Ryan Trinkle
-
Simon Peter Nicholls