Consider the following code:
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.HList.GhcSyntax((.!.),(.=.),(.*.))
import Data.HList.Record(emptyRecord)
import Data.HList.TypeCastGeneric1
import Data.HList.TypeEqGeneric1
import Data.HList.Label5
data Hello1 = Hello1
data Hello2 = Hello2
record = (Hello1 .=. "Hello1") .*. (Hello2 .=. "Hello2") .*. emptyRecord
f1 = $([| (\r1 -> (r1 .!. Hello1)) |])
main = print $ f1 record
This compiles fine and prints out "Hello1" as expected.
However, adding the following line (GHC 7.4.1) gives a compile error:
f2 = $([| (\r2 -> (r2 .!. Hello2)) |])
The error given is:
error.hs:16:1:
Could not deduce (Data.HList.Record.HasField Hello2 r0 v0)
arising from the ambiguity check for `main'
from the context (Data.HList.Record.HasField Hello2 r v)
bound by the inferred type for `main':
Data.HList.Record.HasField Hello2 r v => IO ()
at error.hs:(16,1)-(20,38)
Possible fix:
add an instance declaration for
(Data.HList.Record.HasField Hello2 r0 v0)
When checking that `main'
has the inferred type `forall r v.
Data.HList.Record.HasField Hello2 r v =>
IO ()'
Probable cause: the inferred type is ambiguous
error.hs:16:1:
Could not deduce (Data.HList.Record.HasField Hello2 r0 v0)
arising from the ambiguity check for `f1'
from the context (Data.HList.Record.HasField Hello2 r v)
bound by the inferred type for `f1':
Data.HList.Record.HasField Hello2 r v =>
Data.HList.Record.Record
(Data.HList.HListPrelude.HCons
(Data.HList.Record.LVPair Hello1 [Char])
(Data.HList.HListPrelude.HCons
(Data.HList.Record.LVPair Hello2 [Char])
Data.HList.HListPrelude.HNil))
-> [Char]
at error.hs:(16,1)-(20,38)
Possible fix:
add an instance declaration for
(Data.HList.Record.HasField Hello2 r0 v0)
When checking that `f1'
has the inferred type `forall r v.
Data.HList.Record.HasField Hello2 r v =>
Data.HList.Record.Record
(Data.HList.HListPrelude.HCons
(Data.HList.Record.LVPair Hello1 [Char])
(Data.HList.HListPrelude.HCons
(Data.HList.Record.LVPair Hello2 [Char])
Data.HList.HListPrelude.HNil))
-> [Char]'
Probable cause: the inferred type is ambiguous
Why does adding the f2
line result in a compile error?
Note: The Template Haskell parts may look silly here, but they are a simplification of more complex Template Haskell which does work on tuples. I've posted the simplest example I could construct that still exhibited the error. I realise removing the Template Haskell fixes the issue in this case, but that isn't an option in my real code.
Edit:
In addition, the following fails to compile. Why is this the case:
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.HList.GhcSyntax((.!.),(.=.),(.*.))
import Data.HList.Record(emptyRecord)
import Data.HList.TypeCastGeneric1
import Data.HList.TypeEqGeneric1
import Data.HList.Label5
data Hello1 = Hello1
data Hello2 = Hello2
data Hello3 = Hello3
record1 = (Hello1 .=. "Hello1") .*. (Hello2 .=. "Hello2") .*. emptyRecord
record2 = (Hello1 .=. "Hello1") .*. (Hello2 .=. "Hello2") .*. (Hello3 .=. "Hello3") .*. emptyRecord
f1 = $([| (\r1 -> (r1 .!. Hello1)) |])
main = print $ (f1 record1, f1 record2)
I've found giving your top level functions type signatures fixes any issues. See the code below:
{-# LANGUAGE TemplateHaskell #-}
module X where
import Data.HList.GhcSyntax((.!.))
f = [| (\x r -> (r .!. x)) |]
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE FlexibleContexts #-}
import Data.HList.GhcSyntax((.!.),(.=.),(.*.))
import Data.HList.Record(emptyRecord)
import Data.HList.TypeCastGeneric1
import Data.HList.TypeEqGeneric1
import Data.HList.Label5
import X
import Data.HList.Record (HasField)
data Hello1 = Hello1
data Hello2 = Hello2
data Hello3 = Hello3
record1 = (Hello1 .=. "Hello1") .*. (Hello2 .=. "Hello2") .*. emptyRecord
record2 = (Hello1 .=. "Hello1") .*. (Hello2 .=. "Hello2") .*. (Hello3 .=. "Hello3") .*. emptyRecord
g1 :: (HasField Hello1 a b) => a -> b -- Type signature here
g1 = $(f) Hello1
g2 :: (HasField Hello2 a b) => a -> b -- Type signature here
g2 = $(f) Hello2
main = print $ (g1 record1, g2 record1, g1 record2, g2 record2)