[Haskell-cafe] Beginner's TH question

Miguel Mitrofanov miguelimo38 at yandex.ru
Sat Dec 20 12:38:40 EST 2008


Seems like GHC had already told you what's wrong. Instance  
declarations like "instance UIState t" are illegal without  
FlexibleInstances language feature enabled. Also, I don't quite  
understand, what you're trying to achieve; argument "t" and the letter  
"t" in the TH body are two different beasts, so your "derive..." would  
be of no use.

May be, you want something like this:

{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
class C a where c :: a -> a
deriveC t =
      do decs <- [d| c x = x |]
        tp <- t
        return [InstanceD [] (AppT (ConT ''C) tp) decs]

{-# LANGUAGE TemplateHaskell #-}
module THTest where
import TH
$(deriveC [t| Int |])

*THTest> c (1 :: Int)
1

On 20 Dec 2008, at 18:59, Jeff Heard wrote:

> Two things...  can I add fields to records using Template Haskell,  
> like:
>
> data T = T { $fields, myfield :: Field, ... }
>
> I assume the answer there is no, and then what's wrong with this?  I  
> get:
>
>    Illegal instance declaration for `UIState t'
>        (All instance types must be of the form (T a1 ... an)
>         where a1 ... an are type *variables*,
>         and each type variable appears at most once in the instance  
> head.
>         Use -XFlexibleInstances if you want to disable this.)
>    In the instance declaration for `UIState t'
>    In the expression:
>        [d|
>            instance UIState t where
>                { setSizeY v a = setSizeY v . uist $ a
>                  setSizeX v a = setSizeX v . uist $ a
>                  setDrawing v a = setDrawing v . uist $ a
>                  setKey v a = setKey v . uist $ a
>                  .... } |]
>    In the definition of `deriveUIState':
>        deriveUIState uist t
>                        = [d|
>                              instance UIState t where
>                                  { setSizeY v a = setSizeY v . uist  
> $ a
>                                    setSizeX v a = setSizeX v . uist  
> $ a
>                                    setDrawing v a = setDrawing v .  
> uist $ a
>                                    .... } |]
>
> in this module:
>
> -# LANGUAGE TemplateHaskell #-}
> module Graphics.Rendering.Thingie.TH where
>
> import Language.Haskell.TH
> import Graphics.Rendering.Thingie.UIState
> import qualified Graphics.Rendering.Thingie.BasicUIState as S
>
>
> deriveUIState uist t =
>      [d| instance UIState t where
>            mousePosition a = S.mousePosition . uist $ a
>            mouseLeftButtonDown a = S.mouseLeftButtonDown . uist $ a
>            mouseRightButtonDown a = S.mouseRightButtonDown . uist $ a
>            mouseMiddleButtonDown a = S.mouseMiddleButtonDown . uist  
> $ a
>            mouseLeftButtonClicked a = S.mouseLeftButtonClicked .  
> uist $ a
>            mouseRightButtonClicked a = S.mouseRightButtonClicked .  
> uist $ a
>            mouseMiddleButtonClicked a = S.mouseMiddleButtonClicked .  
> uist $ a
>            mouseWheel a = S.mouseWheel . uist $ a
>            keyCtrl a = S.keyCtrl . uist $ a
>            keyShift a = S.keyShift . uist $ a
>            keyAlt a = S.keyAlt . uist $ a
>            key a = S.key . uist $ a
>            drawing a = S.drawing . uist $ a
>            sizeX a = S.sizeX . uist $ a
>            sizeY a = S.sizeY . uist $ a
>            setMousePosition v a = setMousePosition v . uist $ a
>            setMouseLeftButtonDown v a = setMouseLeftButtonDown v .  
> uist $ a
>            setMouseRightButtonDown v a = setMouseRightButtonDown v .  
> uist $ a
>            setMouseMiddleButtonDown v a = setMouseMiddleButtonDown  
> v . uist $ a
>            setMouseLeftButtonClicked v a = setMouseLeftButtonClicked
> v . uist $ a
>            setMouseRightButtonClicked v a =
> setMouseRightButtonClicked v . uist $ a
>            setMouseMiddleButtonClicked v a =
> setMouseMiddleButtonClicked v . uist $ a
>            setMouseWheel v a = setMouseWheel v . uist $ a
>            setKeyCtrl v a = setKeyCtrl v . uist $ a
>            setKeyShift v a = setKeyShift v . uist $ a
>            setKeyAlt v a = setKeyAlt v . uist $ a
>            setKey v a = setKey v . uist $ a
>            setDrawing v a = setDrawing v . uist $ a
>            setSizeX v a = setSizeX v . uist $ a
>            setSizeY v a = setSizeY v . uist $ a
>       |]
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list