tuple (Int) == or != Int ?
Does ghc make difference beteen a tuple "(Int)" and a no tuple "Int" ? I'm confused about this error: -- packages: template-haskell {-# OPTIONS_GHC -XTemplateHaskell #-} module Main where import Language.Haskell.TH import System.IO import Language.Haskell.TH.Syntax class PrimaryKey tableRow pk | tableRow -> pk where pk :: tableRow -> pk data Row = Row { idV :: Int , b :: String } $( do let pks = ["idV"] row <- newName "row" {- || instance PrimaryKey Row ((GHC.Base.Int)) || where pk row_0 = (idV row_0) test.hs|15 col 3 error| || Couldn't match expected type `(Int)' against inferred type `Int' || In the expression: idV row[a1eY] || In the definition of `pk': pk row[a1eY] = idV row[a1eY] || In the definition for method `pk' -} i <- instanceD (cxt []) (appT (appT (conT $ mkName $ "PrimaryKey") (conT $ ''Row)) (appT (tupleT (length pks)) (conT ''Int))) [funD (mkName "pk") [clause [varP row] (normalB (tupE (map (\k -> (appE (varE $ mkName $ k) (varE row))) pks))) []]] runIO $ do putStrLn $ pprint $ i hFlush stdout return [i] ) main = return () Marc Weber
On Sun, Jun 29, 2008 at 4:01 PM, Marc Weber
Does ghc make difference beteen a tuple "(Int)" and a no tuple "Int" ?
Unfortunately, Template Haskell makes a difference, which IMHO is a bug (http://hackage.haskell.org/trac/ghc/ticket/2358 ). It would be a good idea to add yourself to the CC list of the ticket.
Thanks. Alfonso pointed this same thing out recently, and I fixed it. Now (Int) and Int should be the same. http://hackage.haskell.org/trac/ghc/ticket/2358 Should be OK now in the HEAD at least. Simon | -----Original Message----- | From: template-haskell-bounces@haskell.org [mailto:template-haskell-bounces@haskell.org] On Behalf Of | Marc Weber | Sent: 29 June 2008 22:02 | To: template-haskell@haskell.org | Subject: [Template-haskell] tuple (Int) == or != Int ? | | Does ghc make difference beteen a tuple "(Int)" and a no tuple "Int" ? | I'm confused about this error: | | -- packages: template-haskell | {-# OPTIONS_GHC -XTemplateHaskell #-} | module Main where | import Language.Haskell.TH | import System.IO | import Language.Haskell.TH.Syntax | | class PrimaryKey tableRow pk | tableRow -> pk where pk :: tableRow -> pk | | data Row = Row { | idV :: Int | , b :: String | } | | $( do let pks = ["idV"] | row <- newName "row" | {- | || instance PrimaryKey Row ((GHC.Base.Int)) | || where pk row_0 = (idV row_0) | test.hs|15 col 3 error| | || Couldn't match expected type `(Int)' against inferred type `Int' | || In the expression: idV row[a1eY] | || In the definition of `pk': pk row[a1eY] = idV row[a1eY] | || In the definition for method `pk' | -} | i <- instanceD (cxt []) (appT (appT (conT $ mkName $ "PrimaryKey") (conT $ ''Row)) (appT (tupleT | (length pks)) (conT ''Int))) | [funD (mkName "pk") [clause [varP row] (normalB (tupE (map (\k -> (appE (varE $ mkName $ | k) (varE row))) pks))) []]] | runIO $ do putStrLn $ pprint $ i | hFlush stdout | return [i] | ) | main = return () | | Marc Weber | _______________________________________________ | template-haskell mailing list | template-haskell@haskell.org | http://www.haskell.org/mailman/listinfo/template-haskell
participants (3)
-
Alfonso Acosta -
Marc Weber -
Simon Peyton-Jones