A quick follow-up: 1) I had a typo: it should say "N4 is like N1 with a phantom type variable".
2) In my larger code base, the constructor that is visible to TH when I think it shouldn't be is part of a type that is alpha-equivalent to N3. It's odd that N3 doesn't exhibit the leakiness here but an alpha-equivalent type does exhibit it in my larger program. On Fri, May 27, 2011 at 12:04 PM, Nicolas Frisby <nicolas.fri...@gmail.com> wrote: > With the three modules at the end of this email, I get some > interesting results. Note that none of the constructors are exported, > yet Template Haskell can see (and splice in variable occurrences of!) > T, C2, W1, and W4. > > If you load Dump into GHCi, you get to see the Info that TH provides > when you reify each of the data types. For T, T2, N1, and N4, their > construct is visible in the Info even though M doesn't export it. > > As a consequence, you can load Unhide with no errors. Thus c = C, c2 = > C2, w1 = N1, and w4 = N4, even though those constructors were not > supposed to be imported. > > I couldn't find any mention of this on the GHC Trac for Template > Haskell or for a general search of "reify". > > * http://j.mp/l9Ztjz (Description contains "reify") > * http://j.mp/mprUmq (Component = Template Haskell) > * Disclaimer: I didn't take the time to inspect this one > http://hackage.haskell.org/trac/ghc/ticket/4946 > > T is isomorphic to (), T2 is like T with a phantom type argument, N1 > is a newtype wrapping an Int, and N4 is like N3 with a phantom type > variable. This seems too inconsistent to be an intended behavior. Am I > missing something? Thanks. > > ==> M.hs <== > module M (T(), T1(), T2(), T3(), T4(), N1(), N3(), N4()) where > > data T = C > data T1 = C1 Int > data T2 a = C2 > data T3 a = C3 a > data T4 a = C4 Int > newtype N1 = W1 Int > newtype N3 a = W3 a > newtype N4 a = W4 Int > > ==> Dump.hs <== > {-# LANGUAGE TemplateHaskell #-} > > module Dump where > > import Language.Haskell.TH > import M > > dumpT, dumpT1, dumpT2, dumpT3, dumpT4, dumpN1, dumpN3, dumpN4 :: () > dumpT = $(reify ''T >>= fail . show) > dumpT1 = $(reify ''T1 >>= fail . show) > dumpT2 = $(reify ''T2 >>= fail . show) > dumpT3 = $(reify ''T3 >>= fail . show) > dumpT4 = $(reify ''T4 >>= fail . show) > dumpN1 = $(reify ''N1 >>= fail . show) > dumpN3 = $(reify ''N3 >>= fail . show) > dumpN4 = $(reify ''N4 >>= fail . show) > > ==> Unhide.hs <== > {-# LANGUAGE TemplateHaskell #-} > > module Unhide where > > import Language.Haskell.TH > import M > > c :: T > c = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) -> ConE n) `fmap` reify ''T) > c2 :: T2 a > c2 = $((\(TyConI (DataD _ _ _ [NormalC n _] _)) -> ConE n) `fmap` reify ''T2) > w1 :: Int -> N1 > w1 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) -> ConE n) `fmap` reify > ''N1) > w4 :: Int -> N4 a > w4 = $((\(TyConI (NewtypeD _ _ _ (NormalC n _) _)) -> ConE n) `fmap` reify > ''N4) > > > > ----- for convenience, this is what I get when I load Dump in ghci > > Dump.hs:9:11: > TyConI (DataD [] M.T [] [NormalC M.C []] []) > In the expression: $(reify 'T >>= fail . show) > In an equation for `dumpT': dumpT = $(reify 'T >>= fail . show) > > Dump.hs:10:12: > TyConI (DataD [] M.T1 [] [] []) > In the expression: $(reify 'T1 >>= fail . show) > In an equation for `dumpT1': dumpT1 = $(reify 'T1 >>= fail . show) > > Dump.hs:11:12: > TyConI (DataD [] M.T2 [PlainTV a_1627390697] [NormalC M.C2 []] []) > In the expression: $(reify 'T2 >>= fail . show) > In an equation for `dumpT2': dumpT2 = $(reify 'T2 >>= fail . show) > > Dump.hs:12:12: > TyConI (DataD [] M.T3 [PlainTV a_1627390696] [] []) > In the expression: $(reify 'T3 >>= fail . show) > In an equation for `dumpT3': dumpT3 = $(reify 'T3 >>= fail . show) > > Dump.hs:13:12: > TyConI (DataD [] M.T4 [PlainTV a_1627390695] [] []) > In the expression: $(reify 'T4 >>= fail . show) > In an equation for `dumpT4': dumpT4 = $(reify 'T4 >>= fail . show) > > Dump.hs:14:12: > TyConI (NewtypeD [] M.N1 [] (NormalC M.W1 [(NotStrict,ConT > GHC.Types.Int)]) []) > In the expression: $(reify 'N1 >>= fail . show) > In an equation for `dumpN1': dumpN1 = $(reify 'N1 >>= fail . show) > > Dump.hs:15:12: > TyConI (DataD [] M.N3 [PlainTV a_1627390694] [] []) > In the expression: $(reify 'N3 >>= fail . show) > In an equation for `dumpN3': dumpN3 = $(reify 'N3 >>= fail . show) > > Dump.hs:16:12: > TyConI (NewtypeD [] M.N4 [PlainTV a_1627390693] (NormalC M.W4 > [(NotStrict,ConT GHC.Types.Int)]) []) > In the expression: $(reify 'N4 >>= fail . show) > In an equation for `dumpN4': dumpN4 = $(reify 'N4 >>= fail . show) > Failed, modules loaded: M. > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe