Re: Socket library ghc 5.02.1

2001-11-27 Thread Sven Eric Panitz



 From: Sigbjorn Finne [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 References: [EMAIL PROTECTED]
 Date: Mon, 26 Nov 2001 12:30:47 -0800

Sven Eric Panitz [EMAIL PROTECTED] writes:
  
  It seems that the Socket library does still not work
  with ghc 5.02.1.
  I tried the simple test:
  
   main =
   do
   d - connectTo localhost (PortNumber 80)
   hPutStr d GET / HTTP/1.0\n\n
   hFlush d
   c - hGetContents d
   putStr c
  
  On Windows2000 I get the known error:
  
  *** Exception: does not exist
  Action: getProtocolByName
  Reason: no such protocol entry
  

 (You, of course, need to wrap up that code with Socket.withSocketDo
 to start up WinSock first).

 FYI, in case you're planning on doing socket programming with GHC-5.02
 on a Win32 platform, stay away from using the higher-level Socket module,
 since its IO.Handle based view of sockets is just broken. Stick with the
 lower-level SocketPrim interface instead.

 Specifically, stay away from using the following:

* Socket. connectTo
* Socket.accept
* Socket.sendTo
* Socket. recvFrom
* SocketPrim.socketToHandle

 --sigbjorn


Thanks for the help and valuable information. 

I tried the following little test, which stays away from
above functions:

 module Main where
 
 import BSD
 import SocketPrim
 import Socket (withSocketsDo)

 main =  
  Socket.withSocketsDo
   (do
 protNum - getProtocolNumber tcp
 s - socket AF_INET Stream protNum
 hostAddr - inet_addr 157.189.164.68
 let sAddr =  (SockAddrInet (toEnum 8080) hostAddr)
 connect s sAddr
 i - sendTo  s GET / HTTP/1.0\r\n\r\n sAddr
 (str,l,imsAddr) - recvFrom s 1000
 putStr str
   )


But something I seem to be doing wrong.

During evaluation of 'recvFrom s 1000' I get the following
error message (consistently for unix and windows):

  Fail: SocketPrim.hsc:241: Non-exhaustive patterns in case


As the log of the webserver reveals the sendTo works fine.

Any idea what could be my problem?

Sven Eric


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Socket library ghc 5.02.1

2001-11-27 Thread Sigbjorn Finne


 
 Conclusion: you're hosed with ghc-5.02.1 and its socket libs under
 Win32. Sorry.
 

If you don't mind getting your hands a (little) bit dirty, here's a story
that will work ghc-5.02.1:

* edit SocketPrim.hi (and SocketPrim.p_hi), to instead of saying 
   Socket in its __export section it says Socket{MkSocket}

   (you'll find the .hi file in imports/net/ inside your 5.02.1 tree).

* compile up the attached NetExtra.hs as follows:
  
 foo$ ghc -c NetExtra.hs -fvia-C -fglasgow-exts -package net

* import and include NetExtra with your socket code, e.g.,

main = Socket.withSocketsDo $ do
   protNum - getProtocolNumber tcp
   s - socket AF_INET Stream protNum
   hostAddr - inet_addr 127.0.0.1
   let sAddr =  (SockAddrInet 80 hostAddr)
   connect s sAddr
   send s GET / HTTP/1.0\r\n\r\n
   str - recvAll s
   putStr str

recvAll :: Socket - IO String
recvAll sock = do
 str - catch (recv s 100) (\ _ - return )
 case str of
   - return str
  _  - do
 ls - recvAll sock
 return (str ++ ls)


hth
--sigbjorn




NetExtra.hs
Description: Binary data


Casting dynamic values

2001-11-27 Thread George Russell

It would occasionally be nice to have a function
   cast :: (Typeable a,Typeable b) = a - Maybe b
which returns Just a if a and b have the same type, and Nothing otherwise.
This may seem rather a curious need, but it arises with existential
types; if you have
   data A = forall a . (context) = A a
(context including Typeable a) then this allows you to
getB :: (Typeable b) = A - Maybe b
getB (A a) = cast a

and so extract a value from A, if you can guess its type.

Clearly we can implement
   cast = fromDynamic . toDyn

My question is: is this the most efficient way of doing it, or is there
a better way?

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Casting dynamic values

2001-11-27 Thread Alastair David Reid


George Russell [EMAIL PROTECTED] writes:

 cast :: (Typeable a,Typeable b) = a - Maybe b
 cast = fromDynamic . toDyn

 My question is: is this the most efficient way of doing it, or is
 there a better way?

I think I'd do it that way.  toDyn and fromDynamic are both pretty
simple functions.

  toDyn x pairs x with a representation of its type.
  fromDynamic checks the type is correct and returns x.

That is, the cost is:

1. construct the representation of type a
2. construct the pair
3. deconstruct the pair
4. construct the representation of type b
5. compare the representations of types a and b

If GHC is able to inline these functions, construction and
deconstruction of the pair can probably be eliminated.  

That leaves just building the representations and comparing them.  I
believe GHC could construct the representations at compile time - all
it has to do is inline some pretty-trivial method bodies.

It'd be nice if GHC could perform some parts of the comparision at
compile time.  For example:

   Int =?= Int-  True
   Int =?= Float  -  False
   [a] =?= [b]-  [a] =?= [b]

But I don't think GHC can do this because AFAIK, GHC will not reduce
literal string comparisions at compile time.

   Int == Int   -  True
   Int == Float -  False
   App List a == App List b -  List == List  a == b
-  True  a == b
-  a == b

[This is assuming that GHC's implementation of Typeof still uses
strings.  This may not be true though since there was talk of adding
direct compiler support to make the implementation of typeof more
efficient and, more importantly, less prone to programmer error.  The
motivation to do this was the realization that one could break type
safety by writing a bad instance of typeof.]

-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users