Source code location in IO?

Is it compatible with the semantics of Haskell to have a function sourceLocation :: IO String which when run returns the source file location at which it is used? For example, suppose Main.hs is module Main where main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation It would print the following when run Main.hs:4 Hello Main.hs:6 and module Main where main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s It would print the following when run Main.hs:4 Hello Main.hs:4 If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run? Tom

It feels weird to me that this program transformation produces
different output, and I can't seem to think of another IO action that
behaves this way. Essentially, you'd want `IO a` to have different
semantics from other `a`s, in that let binding it changes what it
does.
However, you can do this with the `qLocation` Template Haskell
function in Language.Haskell.TH.Syntax. Does that help?
Erik
On 20 June 2016 at 17:03, Tom Ellis
Is it compatible with the semantics of Haskell to have a function
sourceLocation :: IO String
which when run returns the source file location at which it is used? For example, suppose Main.hs is
module Main where
main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation
It would print the following when run
Main.hs:4 Hello Main.hs:6
and
module Main where
main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s
It would print the following when run
Main.hs:4 Hello Main.hs:4
If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run?
Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Mon, Jun 20, 2016 at 05:14:45PM +0200, Erik Hesselink wrote:
It feels weird to me that this program transformation produces different output, and I can't seem to think of another IO action that behaves this way. Essentially, you'd want `IO a` to have different semantics from other `a`s, in that let binding it changes what it does.
It's definitely weird, but it seems consistent with some behaviour we see around lazy IO, Cf these threads https://mail.haskell.org/pipermail/haskell/2009-March/021064.html https://mail.haskell.org/pipermail/haskell/2009-March/021071.html
However, you can do this with the `qLocation` Template Haskell function in Language.Haskell.TH.Syntax. Does that help?
I meant it more as a sort of theoretical question.
On 20 June 2016 at 17:03, Tom Ellis
wrote: Is it compatible with the semantics of Haskell to have a function
sourceLocation :: IO String
which when run returns the source file location at which it is used? For example, suppose Main.hs is
module Main where
main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation
It would print the following when run
Main.hs:4 Hello Main.hs:6
and
module Main where
main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s
It would print the following when run
Main.hs:4 Hello Main.hs:4
If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run?

Source location is typically a preprocessor macro. So it could have the same semantics as a pure Template Haskell function. On Mon, Jun 20, 2016 at 10:20 AM Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Mon, Jun 20, 2016 at 05:14:45PM +0200, Erik Hesselink wrote:
It feels weird to me that this program transformation produces different output, and I can't seem to think of another IO action that behaves this way. Essentially, you'd want `IO a` to have different semantics from other `a`s, in that let binding it changes what it does.
It's definitely weird, but it seems consistent with some behaviour we see around lazy IO, Cf these threads
https://mail.haskell.org/pipermail/haskell/2009-March/021064.html https://mail.haskell.org/pipermail/haskell/2009-March/021071.html
However, you can do this with the `qLocation` Template Haskell function in Language.Haskell.TH.Syntax. Does that help?
I meant it more as a sort of theoretical question.
On 20 June 2016 at 17:03, Tom Ellis
wrote: Is it compatible with the semantics of Haskell to have a function
sourceLocation :: IO String
which when run returns the source file location at which it is used? For example, suppose Main.hs is
module Main where
main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation
It would print the following when run
Main.hs:4 Hello Main.hs:6
and
module Main where
main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s
It would print the following when run
Main.hs:4 Hello Main.hs:4
If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run?
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

If it's a practical question, rather than a theoretical one, I use
this: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts...
On Mon, Jun 20, 2016 at 8:03 AM, Tom Ellis
Is it compatible with the semantics of Haskell to have a function
sourceLocation :: IO String
which when run returns the source file location at which it is used? For example, suppose Main.hs is
module Main where
main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation
It would print the following when run
Main.hs:4 Hello Main.hs:6
and
module Main where
main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s
It would print the following when run
Main.hs:4 Hello Main.hs:4
If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run?
Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

It's totally compatible with Haskell semantics, since Haskell does not give any semantics to IO. Anything can happen when you do IO. But it's still a bit weird. :) -----Original Message----- From: Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Tom Ellis Sent: 20 June 2016 16:04 To: haskell-cafe@haskell.org Subject: [Haskell-cafe] Source code location in IO? Is it compatible with the semantics of Haskell to have a function sourceLocation :: IO String which when run returns the source file location at which it is used? For example, suppose Main.hs is module Main where main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation It would print the following when run Main.hs:4 Hello Main.hs:6 and module Main where main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s It would print the following when run Main.hs:4 Hello Main.hs:4 If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run? Tom _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at http://www.standardchartered.com/en/incorporation-details.html Insofar as this communication contains any market commentary, the market commentary has been prepared by sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied for any other purpose, and is subject to the relevant disclaimers available at http://wholesalebanking.standardchartered.com/en/utility/Pages/d-mkt.aspx Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign on the term sheet to acknowledge in respect of the same. Please visit http://wholesalebanking.standardchartered.com/en/capabilities/financialmarke... for important information with respect to derivative products.

Is it compatible with the semantics of Haskell to have a function sourceLocation :: IO String which when run returns the source file location at which it is used? It's totally compatible with Haskell semantics, since Haskell does not give any semantics to IO. Anything can happen when you do IO. But it's still a bit weird. :)
I think the weird feeling stems exactly from the fact that IO has no well-defined syntax. It's our convenient catch-all for anything remotely un-pure. Nondeterminism? Put it in IO! (Instead of a purely nondeterministic context) Non-destructive read access to a file? Put it in IO! (instead of adding Maybe to a nondeterministic context) Deterministic fire-and-forget write access to a log file? Put it in IO! (instead of a context that just provides an ordering) Firing missiles or calling the system to do an "rm -rf /"? Put it in IO! (instead of a System.Unsafe.Extras.Hidden.Unsafe.Very.WarningUnsafeDontTouchWhyDoWeEvenHaveThisOMGGetAwayFromMe) So let's just view IO as a shorthand for some unknown as-yet unspecified monad stack. (But note that most of the contexts I mentioned don't even need to be monadic) This is not to say IO is not good to have in this form. It's just not a helpful context to answer this question. From this vantage point a possibly better form of the question would be: Could we define a context which contains the required semantics that is consistent with Haskell syntax? Something like thisLine :: SourceInfo Int Of course once you have such a context you can just assume it's part of IO because everything is part of IO. To answer the modified question just think about these facts: 1. We can define contexts with 100% determinism across almost any transformation including changing all the source code around it, the compiler, the language version, and all optimizations. (pure functions, i.e. the Identity context) 2. We can also define contexts with almost 100% non-determinism even across two consecutive invocations with nothing else changed. (calls to external random number generators) 3. The context we are searching for would be deterministic across an intermediate subset of meta-transformations. So if these special semantics were not allowed we would have an inconsistent scale of determinism across meta-transformations, and that would need some serious explaining. Ergo it should be allowed. This trail of thought does bring up two interesting follow-up questions though: Is the hidden structure of the IO stack tightly bound to a theory of consistency across meta-transformations? And do we even have a suitable theory of such transformations if we would want to refine IO? I have no idea. MarLinn

A year has passed and I have just discovered that you had exactly the same idea two years before me! http://augustss.blogspot.se/2014/04/haskell-error-reporting-with-locations_5... On Tue, Jun 21, 2016 at 01:45:13AM +0000, Augustsson, Lennart wrote:
It's totally compatible with Haskell semantics, since Haskell does not give any semantics to IO. Anything can happen when you do IO. But it's still a bit weird. :)
-----Original Message----- From: Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Tom Ellis Sent: 20 June 2016 16:04 To: haskell-cafe@haskell.org Subject: [Haskell-cafe] Source code location in IO?
Is it compatible with the semantics of Haskell to have a function
sourceLocation :: IO String
which when run returns the source file location at which it is used? For example, suppose Main.hs is
module Main where
main = do putStrLn =<< sourceLocation putStrLn "Hello" putStrLn =<< sourceLocation
It would print the following when run
Main.hs:4 Hello Main.hs:6
and
module Main where
main = do let s = sourceLocation putStrLn =<< s putStrLn "Hello" putStrLn =<< s
It would print the following when run
Main.hs:4 Hello Main.hs:4
If this is not compatible with the semantics of Haskell, why not? I agree that the two programs must have the same denotation, but is there anything that requires them to have the same output when run?
participants (6)
-
Anatoly Yakovenko
-
Augustsson, Lennart
-
Erik Hesselink
-
Evan Laforge
-
MarLinn
-
Tom Ellis