Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  A seemingly simple use-case for Template     Haskell (Mario Lang)
   2. Re:  A seemingly simple use-case for Template Haskell
      (Frerich Raabe)


----------------------------------------------------------------------

Message: 1
Date: Wed, 28 Sep 2016 17:12:15 +0200
From: Mario Lang <ml...@delysid.org>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] A seemingly simple use-case for
        Template        Haskell
Message-ID: <87wphw6ots....@fx.delysid.org>
Content-Type: text/plain; charset=utf-8

Ryan Trinkle <ryan.trin...@gmail.com> writes:

> 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 <ml...@delysid.org> 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,
  ⡍⠁⠗⠊⠕


------------------------------

Message: 2
Date: Thu, 29 Sep 2016 10:39:14 +0200
From: Frerich Raabe <ra...@froglogic.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] A seemingly simple use-case for
        Template Haskell
Message-ID: <2f0d2bcda1b619f8284c0891002f9...@roundcube.froglogic.com>
Content-Type: text/plain; charset=US-ASCII; format=flowed

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-Haskell-TH-Syntax.html#t:Dec

...and then work my way down. Hope that helps!

-- 
Frerich Raabe - ra...@froglogic.com
www.froglogic.com - Multi-Platform GUI Testing


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 99, Issue 22
*****************************************

Reply via email to