
jerzy.karczmarczuk@info.unicaen.fr wrote:
Yes, *different approach*. So, there *are* differences. Compilers, anyway, are special applications. I wanted to see - responding to Brandon - a "normal" Haskell program, which does IO without monads, that't all. The problem is then when you hide something, you hide. It is possible to superpose a kind of monadic framework on unique worlds, files, etc. in Clean, but the reverse operation goes beyond my horizons. Some examples, anybody? Jerzy Karczmarczuk Ah yes, I see what you mean now. I have no idea, I guess only unsafePerformIO will allow you to do something like that... But that will completely break referential transparency. But I really don't know. What do the experts have to say?

On Oct 15, 2007, at 13:32 , Peter Verswyvelen wrote:
Yes, *different approach*. So, there *are* differences. Compilers, anyway, are special applications. I wanted to see - responding to Brandon - a "normal" Haskell program, which does IO without monads, that't all. The problem is then when you hide something, you hide. It is possible to superpose a kind of monadic framework on unique worlds, files, etc. in Clean, but the reverse operation goes beyond my horizons. Some examples, anybody? Ah yes, I see what you mean now. I have no idea, I guess only unsafePerformIO will allow you to do something like that... But
jerzy.karczmarczuk@info.unicaen.fr wrote: that will completely break referential transparency. But I really don't know. What do the experts have to say?
Use the source of unsafePerformIO as an example of how to write code which passes around RealWorld explicitly, but without unencapsulating it like unsafePerformIO does. The main problem here, I think, is that because all the GHC runtime's functions that interact with RealWorld (aside from unsafe*IO) are themselves only exported wrapped up in IO, you can't (as far as I know) get at the lower level internal (e.g.) putStrLn' :: RealWorld -
String -> (# RealWorld,() #) to do I/O in a direct/explicit/non- monadic style. In theory, one could export those and use them directly.
(Actually, as a practical matter, IIRC GHC "knows about" RealWorld and removes all of it when generating cmm code once it's done the job of sequencing Haskell evaluation; I'm not sure how well that would work if you wrote I/O in direct/explicit style. unsafePerformIO doesn't really count for that because it removes the RealWorld itself.) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Oct 15, 2007, at 13:32 , Peter Verswyvelen wrote:
jerzy.karczmarczuk@info.unicaen.fr wrote:
Yes, *different approach*. So, there *are* differences. Compilers, anyway, are special applications. I wanted to see - responding to Brandon - a "normal" Haskell program, which does IO without monads, that't all. The problem is then when you hide something, you hide. It is possible to superpose a kind of monadic framework on unique worlds, files, etc. in Clean, but the reverse operation goes beyond my horizons. Some examples, anybody? Ah yes, I see what you mean now. I have no idea, I guess only unsafePerformIO will allow you to do something like that... But that will completely break referential transparency. But I really don't know. What do the experts have to say?
Use the source of unsafePerformIO as an example of how to write code which passes around RealWorld explicitly, but without unencapsulating it like unsafePerformIO does.
The main problem here, I think, is that because all the GHC runtime's functions that interact with RealWorld (aside from unsafe*IO) are themselves only exported wrapped up in IO, you can't (as far as I know) get at the lower level internal (e.g.) putStrLn' :: RealWorld -> String -> (# RealWorld,() #) to do I/O in a direct/explicit/non-monadic style. In theory, one could export those and use them directly.
Well, if you import GHC.IOBase then you get
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #)) unIO (IO a) = a
Then the type of putStrLn: -- putStrLn :: String -> IO () means that putStrLn' can be defined as putStrLn' :: String -> State# RealWorld -> (# State# RealWorld, a #) putStrLn' = unIO . putStrLn Now you have the unboxed tuple and need to work with many 'case' statements to accomplish anything. Also you need to get you hand on State# RealWorld either (1) Honestly, by wrapping your code in IO again and using it normally (2) From a copy, via unsafeInterleaveIO (3) From nowhere, via unsafePerformIO
(Actually, as a practical matter, IIRC GHC "knows about" RealWorld and removes all of it when generating cmm code once it's done the job of sequencing Haskell evaluation; I'm not sure how well that would work if you wrote I/O in direct/explicit style. unsafePerformIO doesn't really count for that because it removes the RealWorld itself.)

On Oct 15, 2007, at 19:00 , ChrisK wrote:
Brandon S. Allbery KF8NH wrote:
Use the source of unsafePerformIO as an example of how to write code which passes around RealWorld explicitly, but without unencapsulating it like unsafePerformIO does.
The main problem here, I think, is that because all the GHC runtime's functions that interact with RealWorld (aside from unsafe*IO) are themselves only exported wrapped up in IO, you can't (as far as I know) get at the lower level internal (e.g.) putStrLn' :: RealWorld -> String -> (# RealWorld,() #) to do I/O in a direct/explicit/non-monadic style. In theory, one could export those and use them directly.
Well, if you import GHC.IOBase then you get
newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #)) unIO (IO a) = a
Then the type of putStrLn:
-- putStrLn :: String -> IO ()
means that putStrLn' can be defined as
putStrLn' :: String -> State# RealWorld -> (# State# RealWorld, a #) putStrLn' = unIO . putStrLn
Now you have the unboxed tuple and need to work with many 'case' statements to accomplish anything.
Also you need to get you hand on State# RealWorld either (1) Honestly, by wrapping your code in IO again and using it normally (2) From a copy, via unsafeInterleaveIO (3) From nowhere, via unsafePerformIO
(4) Honestly but unwrapped, by defining "main" in the same desugared way (takes State# RealWorld and returns (# State# RealWorld,a #) (or (# State# RealWorld,() #) if you stick to the H98 definition of main's type), allowing the runtime to pass it in and otherwise not doing anything other than propagating it. My real problem was that I incorrectly recalled IO's type to be based on ST, not State (i.e. had a forall to prevent anything from being able to do anything to/with the State# RealWorld other than pass it on unchanged without triggering a type error). I should have realized that was wrong because unsafePerformIO is itself expressible in Haskell (-fglasgow-exts is needed to make # an identifier character and to enable unboxed types and unboxed tuples, but does not make it possible to cross an existential type barrier). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 10/15/07, ChrisK
Also you need to get you hand on State# RealWorld either (1) Honestly, by wrapping your code in IO again and using it normally (2) From a copy, via unsafeInterleaveIO (3) From nowhere, via unsafePerformIO
Or you can get it honestly via lifting: liftRawIO :: (State# RealWorld -> (# State# RealWorld, a #)) -> IO a liftRawIO = GHC.IOBase.IO main = liftRawIO rawMain rawMain :: State# RealWorld-> (# State# RealWorld, () #) {- implement rawMain here -} -- ryan

On Oct 15, 2007, at 21:01 , Ryan Ingram wrote:
Oops, I read too fast, you mentioned that as #1.
On 10/15/07, ChrisK
wrote: Also you need to get you hand on State# RealWorld either (1) Honestly, by wrapping your code in IO again and using it normally
Silly me.
That makes two of us; my (4) is in fact his (1), I misunderstood the "wrapping your code in IO again". For those trying to follow along with all this silliness, the secret to making this work is defining a runIO function --- which is *not* the same as unsafePerformIO, because that invokes the internal RealWorld# constructor to inject a "fresh" State# RealWorld, whereas we're using the one that we were legitimately passed: runIO :: IO a -> State# RealWorld -> (# State# RealWorld,a #) runIO (IO f) s = lazy (f s) (See libraries/base/GHC/IOBase.lhs for why we need the GHC builtin "lazy" there.) The reason for this is that IO is a "state-like" type: newtype IO a = IO (State# RealWorld -> (# State# RealWorld,a #)) Which is to say, it is a wrapper around a function which accepts a state and returns a "modified" (in our case, actually just passed through without even looking at it) state along with the result of a computation. The runIO function is just runState specialized to this newtype. (Because you can't pattern match on (IO (s -> (# s,a #))) in a function definition.) I'm working on a "simple" example of how to do this without treating IO as a monad. So far it's proving a very concrete demonstration to me of why you do *not* want to do it this way, but instead should consider the monad your friend. :) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

I actually got this done several hours ago, but my DSL is being annoying tonight... Anyway, here's a simple example of how to do explicit/non-monadic I/O in GHC. (It *only* works in GHC; other compilers have different internal implementations of IO.) I specifically modeled it to highlight its resemblance to State. {-# OPTIONS_GHC -fno-implicit-prelude -fglasgow-exts #-} import GHC.Base import GHC.IOBase import GHC.IO import GHC.Handle (stdout) {- This is horrible evil to demonstrate how to do I/O without the help of the IO monad. And yes, it is very much a help. The trick here is that the type IO is a state-like type: a value constructor which wraps a function. Thus, working with it manually requires that we have a runIO.(*) Naively, this looks like unsafePerformIO; but in fact it is not, as unsafePerformIO uses the magic builtin RealWorld# to create a new State# RealWorld on the fly, but in fact we are passing on the one we get from somewhere else (ultimately, the initial state for main). (Additionally, we don't unwrap the resulting tuple; we return it.) This is why runIO is really *safePerformIO* (i.e. entirely normal I/O). (*) Well, not absolutely. GHC.IOBase uses unIO instead: unIO (IO f) = f I think this is a little cleaner, and better demonstrates how IO is really not all that special, but simply a way to pass state around. -} -- treat IO like State, for demonstration purposes runIO :: IO a -> State# RealWorld -> (# State# RealWorld,a #) runIO (IO f) s = f s -- And here's our simple "hello, world" demo program main :: IO () main = IO (\s -> runIO (putStrLn' "hello, world") s) -- this is just to demonstrate how to compose I/O actions. we could just -- call the real putStrLn above instead; it is operationally identical. -- write a string followed by newline to stdout -- this is completely normal! putStrLn' :: String -> IO () putStrLn' = hPutStrLn' stdout -- write a string followed by newline to a Handle hPutStrLn' :: Handle -> String -> IO () hPutStrLn' h str = IO (\s -> let (# s',_ #) = runIO (hPutStr' h str) s in runIO (hPutChar h '\n') s') -- write a string, iteratively, to a Handle hPutStr' :: Handle -> String -> IO () hPutStr' _ [] = IO (\s -> (# s,() #)) hPutStr' h (c:cs) = IO (\s -> let (# s',_ #) = runIO (hPutChar h c) s in runIO (hPutStr' h cs) s') -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
ChrisK
-
Peter Verswyvelen
-
Ryan Ingram