[Haskell-cafe] Beginner's TH question

Bulat Ziganshin bulat.ziganshin at gmail.com
Sat Dec 20 11:49:05 EST 2008


Hello Jeff,

Saturday, December 20, 2008, 6:59:42 PM, you wrote:

my experience tells that you should insert whole language sentences,
like

$(add_fields [d| data T = T { myfield :: Field, ... } ] )

where original declaration passed as a parameter


> 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


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list