This is the second of two modules implementing fixed-length vectors in
Haskell. The first used GADTs, a recent extension which currently
requires GHC 6.4. This module uses no extensions to Haskell 98.
This message is literate Haskell. To use, save it as "Vector_H98.lhs".
> module Vector_H98 where
I wrote this up a few days ago and thought I'd share it with the list.
It's yet another implementation of fixed-length vectors (that is, lists
which reflect their length in their type). It's a nice demonstration of
GADTs and an unexpected use of a technique Ralf Hinze describes in
"Generics for the
On 5/5/05, S. Alexander Jacobson <[EMAIL PROTECTED]> wrote:
>
> On Tue, 3 May 2005, Samuel Bronson wrote:
> > Maybe something like
> >
> > from Text.HaXML.XML import (Types, Escape, Pretty)
> >
> > would be nice.
>
> The problem with this one is that you need a way to express all the
> other stuf
Axel Simon wrote:
> > > Does anyone know why these are in the IO monad? Aren't they pure functions
> > > converting between dotted-decimal strings and a 32-bit network byte
> > > ordered
> > > binary value?
>
> I guess the answer is no for both: The first one can fail
That doesn't mean that it
On 5/7/05, Dominic Steinitz <[EMAIL PROTECTED]> wrote:
> > Does anyone know why these are in the IO monad? Aren't they pure functions
> > converting between dotted-decimal strings and a 32-bit network byte ordered
> > binary value?
I guess the answer is no for both: The first one can fail and the
Below is the relevant source code.
David
foreign import ccall unsafe "my_inet_ntoa"
c_inet_ntoa :: HostAddress -> IO (Ptr CChar)
foreign import CALLCONV unsafe "inet_addr"
c_inet_addr :: Ptr CChar -> IO HostAddress
--
Does anyone know why these are in the IO monad? Aren't they pure functions
converting between dotted-decimal strings and a 32-bit network byte ordered
binary value?
Dominic.
http://www.haskell.org/ghc/docs/latest/html/libraries/network/Network.Socket.html#v%3Ainet_addr
http://www.haskell.org/gh