
Hi, I am looking for a way to extend GHCI such that I can do something like this $ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> startMyFunction Prelude> startMyFunction will do a forkIO and listen on a network port for interaction with a remote process and will drop back to GHCI prompt where I can invoke haskell functions that'll control the way the interaction with the remote process occurs. Can this be done? Regards, Kashyap

On 02/04/2011 12:36 PM, C K Kashyap wrote:
Hi, I am looking for a way to extend GHCI such that I can do something like this
$ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> startMyFunction Prelude>
startMyFunction will do a forkIO and listen on a network port for interaction with a remote process and will drop back to GHCI prompt where I can invoke haskell functions that'll control the way the interaction with the remote process occurs. Can this be done? I am not sure that I understand you correctly, but ghci simulates the IO monad, so what about:
Prelude> :l MyModule.hs *MyModule> conn <- waitForAndAcceptConnection *MyModule> someData <- getSomeData conn *MyModule> sendSomeAnswer conn $ processSomeData someData ... -- Steffen
Regards, Kashyap
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks Steffen,
Prelude> :l MyModule.hs *MyModule> conn <- waitForAndAcceptConnection *MyModule> someData <- getSomeData conn *MyModule> sendSomeAnswer conn $ processSomeData someData ...
startMyServer -- at this point the the echo server gets spawned -- echo server continues to run someFunction "hello" --- now onwards hello gets prepended --- echo server continues to run returning "hello"
So this cycle of getting data from the connection and writing answer on the connection should happen concurrently with the ghci interaction ... so lets say that when the "thread" is forked that listens on socket behaves like an echo server ... as in, it reads data from the client till "\n" and echoes it back ... All this would happen without the intervention of the user using GHCI ... However, using GHCI, the user should be able to modify the code such that the server returns "hello" prepended to the input. .. prepended
someFunction "world" --- now onwards "helloworld" get
I hope this is possible without having to modify ghci itself. Regards, Kashyap

On Fri, Feb 4, 2011 at 9:41 AM, C K Kashyap
Thanks Steffen,
Prelude> :l MyModule.hs *MyModule> conn <- waitForAndAcceptConnection *MyModule> someData <- getSomeData conn *MyModule> sendSomeAnswer conn $ processSomeData someData ...
So this cycle of getting data from the connection and writing answer on the connection should happen concurrently with the ghci interaction ... so lets say that when the "thread" is forked that listens on socket behaves like an echo server ... as in, it reads data from the client till "\n" and echoes it back ... All this would happen without the intervention of the user using GHCI ... However, using GHCI, the user should be able to modify the code such that the server returns "hello" prepended to the input. ..
startMyServer -- at this point the the echo server gets spawned -- echo server continues to run someFunction "hello" --- now onwards hello gets prepended --- echo server continues to run returning "hello" prepended someFunction "world" --- now onwards "helloworld" get I hope this is possible without having to modify ghci itself.
Something like this, perhaps. Sorry that it is a bit hard to read. Anthony $ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :m +Data.IORef Control.Concurrent Control.Monad Prelude Data.IORef Control.Concurrent Control.Monad> msg <- newIORef "Hello" Prelude Data.IORef Control.Concurrent Control.Monad> let echo = forever $ readIORef msg >>= putStrLn >> threadDelay 3000000 Prelude Data.IORef Control.Concurrent Control.Monad> t <- forkIO echo Hello Prelude Data.IORef Control.Concurrent Control.Monad> Hello Hello writeIORefHello msg "World" Prelude Data.IORef Control.Concurrent Control.Monad> World World

$ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :m +Data.IORef Control.Concurrent Control.Monad Prelude Data.IORef Control.Concurrent Control.Monad> msg <- newIORef "Hello" Prelude Data.IORef Control.Concurrent Control.Monad> let echo = forever $ readIORef msg >>= putStrLn >> threadDelay 3000000 Prelude Data.IORef Control.Concurrent Control.Monad> t <- forkIO echo Hello Prelude Data.IORef Control.Concurrent Control.Monad> Hello Hello writeIORefHello msg "World" Prelude Data.IORef Control.Concurrent Control.Monad> World World
Thanks ... this is the possibility I was looking for. Btw, I am thinking I'd need to use STM to synchronize right? Regards, Kashyap

On Sun, Feb 6, 2011 at 11:59 PM, C K Kashyap
$ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :m +Data.IORef Control.Concurrent Control.Monad Prelude Data.IORef Control.Concurrent Control.Monad> msg <- newIORef "Hello" Prelude Data.IORef Control.Concurrent Control.Monad> let echo = forever $ readIORef msg >>= putStrLn >> threadDelay 3000000 Prelude Data.IORef Control.Concurrent Control.Monad> t <- forkIO echo Hello Prelude Data.IORef Control.Concurrent Control.Monad> Hello Hello writeIORefHello msg "World" Prelude Data.IORef Control.Concurrent Control.Monad> World World
Thanks ... this is the possibility I was looking for. Btw, I am thinking I'd need to use STM to synchronize right? Regards, Kashyap
You need STM when you need groups of references to change simultaneously as perceived by concurrent processes. Anthony

$ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :m +Data.IORef Control.Concurrent Control.Monad Prelude Data.IORef Control.Concurrent Control.Monad> msg <- newIORef "Hello" Prelude Data.IORef Control.Concurrent Control.Monad> let echo = forever $ readIORef msg >>= putStrLn >> threadDelay 3000000 Prelude Data.IORef Control.Concurrent Control.Monad> t <- forkIO echo Hello Prelude Data.IORef Control.Concurrent Control.Monad> Hello Hello writeIORefHello msg "World" Prelude Data.IORef Control.Concurrent Control.Monad> World World
On my mac, this works..but on Linux, the moment I do t <- forkIO ... , it starts off a thread in the foreground and does not return to the prompt. Regards, Kashyap

On 02/07/2011 12:45 PM, C K Kashyap wrote:
$ ghci GHCi, version 6.12.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Loading package ffi-1.0 ... linking ... done. Prelude> :m +Data.IORef Control.Concurrent Control.Monad Prelude Data.IORef Control.Concurrent Control.Monad> msg <- newIORef "Hello" Prelude Data.IORef Control.Concurrent Control.Monad> let echo = forever $ readIORef msg >>= putStrLn >> threadDelay 3000000 Prelude Data.IORef Control.Concurrent Control.Monad> t <- forkIO echo Hello Prelude Data.IORef Control.Concurrent Control.Monad> Hello Hello writeIORefHello msg "World" Prelude Data.IORef Control.Concurrent Control.Monad> World World
On my mac, this works..but on Linux, the moment I do t <- forkIO ... , it starts off a thread in the foreground and does not return to the prompt.
Strange. Works for me (ghc 6.12.1 on Debian squeeze).

Ok, so someFunction should modify the server's configuration? Maybe you can model it with an IORef like this (untested!):
import Data.IORef
type Config = String -- String to be prepended to every answer
someFunction :: String -> IORef Config -> IORef Config someFunction s r = modifyIORef s (++ s)
startMyServer :: IO (IORef Config) startMyServer = do r <- newIORef "" forkIO $ runServer r return r
runServer :: IORef -> IO () runServer r = do client <- waitForAndAcceptConnection request <- getSomeData client prep <- readIORef r sendSomeAnswer client $ prep ++ request runServer r
And then: *MyModule> r <- startMyServer (plain echo server running) *MyModule> someFunction "hello" r (now echo server with prepend "hello") *MyModule> someFunction "world" r (now echo server with prepend "helloworld") -- Steffen On 02/04/2011 03:41 PM, C K Kashyap wrote:
Thanks Steffen,
Prelude> :l MyModule.hs *MyModule> conn <- waitForAndAcceptConnection *MyModule> someData <- getSomeData conn *MyModule> sendSomeAnswer conn $ processSomeData someData ...
So this cycle of getting data from the connection and writing answer on the connection should happen concurrently with the ghci interaction ... so lets say that when the "thread" is forked that listens on socket behaves like an echo server ... as in, it reads data from the client till "\n" and echoes it back ... All this would happen without the intervention of the user using GHCI ... However, using GHCI, the user should be able to modify the code such that the server returns "hello" prepended to the input. ..
startMyServer -- at this point the the echo server gets spawned -- echo server continues to run someFunction "hello" --- now onwards hello gets prepended --- echo server continues to run returning "hello" prepended someFunction "world" --- now onwards "helloworld" get
I hope this is possible without having to modify ghci itself.
Regards, Kashyap

Hi, I am looking for a way to extend GHCI such that I can do something like this
startMyFunction will do a forkIO and listen on a network port for interaction with a remote process and will drop back to GHCI prompt where I can invoke haskell functions that'll control the way the interaction with the remote process occurs. Can this be done?
What part of that doesn't already work? You can forkIO threads in GHCi, you can listen on the network. If you have written the server so it can be controlled from another thread, you can run those controlling functions at the prompt while the server is working. Brandon

What part of that doesn't already work? You can forkIO threads in GHCi, you can listen on the network. If you have written the server so it can be controlled from another thread, you can run those controlling functions at the prompt while the server is working.
Thanks Brandon .. I was looking for a confirmation.
participants (4)
-
Anthony Cowley
-
Brandon Moore
-
C K Kashyap
-
Steffen Schuldenzucker