[Haskell-cafe] Using Hint with a socket server

Tom Jordan viresh53 at gmail.com
Thu Jun 17 17:35:18 EDT 2010


I'm trying to receive small segments of Haskell code over a socket, and be
able to evaluate them in real time in GHCI.
I've already downloaded Hint and have run the test code, and it's working
great.  I'm also using the socket server code from Ch.27 of "Real World
Haskell"
and that is working well also.

     directly below is the function from the socket server code that handles
the incoming messages.
     Instead of doing this: "putStrLn msg"... I want to send whatever is
captured in "msg" to the GHC interpreter that is used in the Hint code,
something like this:  "eval msg".
     I'm not sure how to combine both of these functionalities to get them
to work with each other..

      -- A simple handler that prints incoming packets
      plainHandler :: HandlerFunc
      plainHandler addr msg =
         putStrLn msg


Below is the full  code for the socket server, then below that is
"SomeModule" used in the Hint example test below that.

-- file: ch27/syslogserver.hs
import Data.Bits
import Network.Socket
import Network.BSD
import Data.List

type HandlerFunc = SockAddr -> String -> IO ()

serveLog :: String              -- ^ Port number or name; 514 is default
         -> HandlerFunc         -- ^ Function to handle incoming messages
         -> IO ()
serveLog port handlerfunc = withSocketsDo $
    do -- Look up the port.  Either raises an exception or returns
       -- a nonempty list.
       addrinfos <- getAddrInfo
                    (Just (defaultHints {addrFlags = [AI_PASSIVE]}))
                    Nothing (Just port)
       let serveraddr = head addrinfos

       -- Create a socket
       sock <- socket (addrFamily serveraddr) Datagram defaultProtocol

       -- Bind it to the address we're listening to
       bindSocket sock (addrAddress serveraddr)

       -- Loop forever processing incoming data.  Ctrl-C to abort.
       procMessages sock
    where procMessages sock =
              do -- Receive one UDP packet, maximum length 1024 bytes,
                 -- and save its content into msg and its source
                 -- IP and port into addr
                 (msg, _, addr) <- recvFrom sock 1024
                 -- Handle it
                 handlerfunc addr msg
                 -- And process more messages
                 procMessages sock

-- A simple handler that prints incoming packets
plainHandler :: HandlerFunc
plainHandler addr msg =
    putStrLn msg


-- main = serveLog "8008" plainHandler
----------------------------------------------------------------------------------------------------------------

module SomeModule(g, h) where

f = head

g = f [f]

h = f

----------------------------------------------------------------------------------------------------------------

import Control.Monad
import Language.Haskell.Interpreter

main :: IO ()
main = do r <- runInterpreter testHint
          case r of
            Left err -> printInterpreterError err
            Right () -> putStrLn "that's all folks"

-- observe that Interpreter () is an alias for InterpreterT IO ()
testHint :: Interpreter ()
testHint =
    do
      say "Load SomeModule.hs"
      loadModules ["SomeModule.hs"]
      --
      say "Put the Prelude, Data.Map and *SomeModule in scope"
      say "Data.Map is qualified as M!"
      setTopLevelModules ["SomeModule"]
      setImportsQ [("Prelude", Nothing), ("Data.Map", Just "M")]
      --
      say "Now we can query the type of an expression"
      let expr1 = "M.singleton (f, g, h, 42)"
      say $ "e.g. typeOf " ++ expr1
      say =<< typeOf expr1
      --
      say $ "Observe that f, g and h are defined in SomeModule.hs, " ++
            "but f is not exported. Let's check it..."
      exports <- getModuleExports "SomeModule"
      say (show exports)
      --
      say "We can also evaluate an expression; the result will be a string"
      let expr2 = "length $ concat [[f,g],[h]]"
      say $ concat ["e.g. eval ", show expr1]
      a <- eval expr2
      say (show a)
      --
      say "Or we can interpret it as a proper, say, int value!"
      a_int <- interpret expr2 (as :: Int)
      say (show a_int)
      --
      say "This works for any monomorphic type, even for function types"
      let expr3 = "\\(Just x) -> succ x"
      say $ "e.g. we interpret " ++ expr3 ++
            " with type Maybe Int -> Int and apply it on Just 7"
      fun <- interpret expr3 (as :: Maybe Int -> Int)
      say . show $ fun (Just 7)
      --
      say "And sometimes we can even use the type system to infer the
expected type (eg Maybe Bool -> Bool)!"
      bool_val <- (interpret expr3 infer `ap` (return $ Just False))
      say (show $ not bool_val)
      --
      say "Here we evaluate an expression of type string, that when
evaluated (again) leads to a string"
      res <- interpret "head $ map show [\"Worked!\", \"Didn't work\"]"
infer >>= flip interpret infer
      say res


say :: String -> Interpreter ()
say = liftIO . putStrLn

printInterpreterError :: InterpreterError -> IO ()
printInterpreterError e = putStrLn $ "Ups... " ++ (show e)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100617/c65df6fc/attachment.html


More information about the Haskell-Cafe mailing list