[Template-haskell] Re: template-haskell names in 6.3
Keean Schupke
k.schupke at imperial.ac.uk
Tue Dec 21 07:08:19 EST 2004
To be honest mkName "Foo.Test" may be enough for what I need
right now...
I don't mean that: mkName "Foo.Test" always equals ''Foo, but I wanted
to make sure it did in the "right" context... IE:
>module Foo
> data Test
>module Bar
>import Foo
> main = putStrLn (''Test == mkName "Foo.Test") -- should print True
>module Bar
>import Foo as Foo'
> main = putStrLn (''Test == mkName "Foo.Test") -- should print False
As to exactly what I am trying to do, it is to take a string say "Test"
and prefix
it with qCurrentModule to give the global name, so that:
module Main
data X
main = do
m <- qCurrentModule
if mkQualName m "X" == ''X -- IE I want to test if m.X is really
the same X as ''X
then putStrLn "Okay"
else putStrLn "Fail"
Keean.
Simon Peyton-Jones wrote:
>Because they the two can behave differently in different contexts. It's
>like saying why doesn't 1==2 because in the context (\x. x>10) both give
>False!
>
>I feel I am missing the point you are trying to make. I thought I had
>it when I suggested mkQualName, and you said "that's exactly what I
>want". But you can define mkQualName easily:
> mkQualName m s = mkName (m ++ "." ++ s).
>
>Why don't you give a complete (but small) example of what you are trying
>to do?
>
>Simon
>
>| -----Original Message-----
>| From: Keean Schupke [mailto:k.schupke at imperial.ac.uk]
>| Sent: 21 December 2004 10:48
>| To: Simon Peyton-Jones
>| Cc: template-haskell at haskell.org
>| Subject: Re: [Template-haskell] Re: template-haskell names in 6.3
>|
>| Okay but:
>|
>| >module Foo where
>| > data Test
>| >
>| >module Bar
>| > import Foo
>| >
>| > test = (''Test == mkName "Foo.Test")
>|
>| Test (in this scope) is Foo.Test, so why shouldn't it equal
>| mkName "Foo.Test" ?
>|
>| Keean.
>|
>|
>| Simon Peyton-Jones wrote:
>|
>| >No, certainly not.
>| >
>| > ''Test :: Name
>| > is a lexically-scoped Name, indissolubly connected to whatever
>| >Test means
>| > in the original lexical scope it appeared in
>| >
>| > mkName "Foo.Test" :: Name
>| > is a dynamically-scoped Name, captured by whatever context it's
>| >spliced into.
>| >
>| >They aren't the same, and shouldn't be!
>| >
>| >Simon
>| >
>| >| -----Original Message-----
>| >| From: template-haskell-bounces at haskell.org
>| >[mailto:template-haskell-bounces at haskell.org] On
>| >| Behalf Of Keean Schupke
>| >| Sent: 21 December 2004 10:06
>| >| To: Simon Peyton-Jones
>| >| Cc: template-haskell at haskell.org
>| >| Subject: Re: [Template-haskell] Re: template-haskell names in 6.3
>| >|
>| >| I think I am already using that... I wasn't sure if the
>'module-part'
>| >of the
>| >| name was the same as in a global name generated from ''... is:
>| >|
>| >| module Foo
>| >| data Test
>| >|
>| >| mkName "Foo.Test" == ''Test -- is this true?
>| >|
>| >| Keean
>| >|
>| >| Simon Peyton-Jones wrote:
>| >|
>| >| >Keean
>| >| >
>| >| >I was half way through implementing this when I realised it's
>there
>| >| >already. If you say
>| >| >
>| >| > mkName "Foo.baz"
>| >| >
>| >| >you'll get a dynamically scoped qualified name, just as you want.
>| >| >
>| >| >Is that OK?
>| >| >
>| >| >Simon
>| >| >
>| >| >| -----Original Message-----
>| >| >| From: template-haskell-bounces at haskell.org
>| >| >[mailto:template-haskell-bounces at haskell.org] On
>| >| >| Behalf Of Keean Schupke
>| >| >| Sent: 03 December 2004 14:38
>| >| >| To: Simon Peyton-Jones
>| >| >| Cc: template-haskell at haskell.org
>| >| >| Subject: Re: [Template-haskell] Re: template-haskell names in
>6.3
>| >| >|
>| >| >| Simon Peyton-Jones wrote:
>| >| >|
>| >| >| >do you mean
>| >| >| > n <- newName s
>| >| >| >or
>| >| >| > let n = mkName s
>| >| >| >?
>| >| >| >
>| >| >| >
>| >| >| I mean the latter... or perhaps: "n <- return $ mkName s"...
>| >| >|
>| >| >| >If the latter, you will get
>| >| >| > data Foo = Foo Foo
>| >| >| >
>| >| >| >... and then I see what you want. You want a version of mkName
>| >that
>| >| >is
>| >| >| >like giving a qualified name in Haskell. It's dynamically
>scoped
>| >| >just
>| >| >| >like mkName, but it obeys the usual rules for qualified names
>in
>| >| >| >Haskell.
>| >| >| >
>| >| >| >To be totally explicit, suppose I have
>| >| >| >
>| >| >| > foo = [| mkQualName "Foo" "baz" |]
>| >| >| >
>| >| >| >then if I call foo thus
>| >| >| >
>| >| >| > wibble = \baz -> $foo
>| >| >| >
>| >| >| >the $foo splice will expand to "Foo.baz", and that won't see
>the
>| >| >\baz;
>| >| >| >it'll see whatever Foo.baz is in scope.
>| >| >| >
>| >| >| >
>| >| >| This is exactly what I am after...
>| >| >|
>| >| >| >Is that what you seek? I can see it's reasonable. I'd need to
>| >add
>| >| >| >
>| >| >| > mkQualName :: String -> String -> Name
>| >| >| >
>| >| >| >That'd mean an extra form of Name. Currently, if you say
>| >| >| > 'Foo.baz
>| >| >| >you'll get a Name whose nameModule isn't necessarily Foo...
>it'll
>| >be
>| >| >the
>| >| >| >module that baz was actually defined in.
>| >| >| >
>| >| >| >
>| >| >| I'll leave that up to you, I don't mind if this translation
>| >happens,
>| >| >as
>| >| >| long as it refers to the Foo.baz in dynamic scope the actuall
>name
>| >| >| can change.
>| >| >|
>| >| >| Keean
>| >| >| _______________________________________________
>| >| >| template-haskell mailing list
>| >| >| template-haskell at haskell.org
>| >| >| http://www.haskell.org/mailman/listinfo/template-haskell
>| >| >
>| >| >
>| >|
>| >| _______________________________________________
>| >| template-haskell mailing list
>| >| template-haskell at haskell.org
>| >| http://www.haskell.org/mailman/listinfo/template-haskell
>| >
>| >
>
>
>
More information about the template-haskell
mailing list