Re: [Haskell-cafe] Basic binary IO

2008-01-20 Thread Jamie Love

Ah, thanks Don, Brandon,


I looked at this but neglected to read through and understand the 
example enough.


Thanks for the tips, they're a great help.


Don Stewart wrote:

jamie.love:
  
bmpHeader = runPut $ do

put 'B'
put 'M'
put (0  :: Int32)
put (0  :: Int32)
put (14 :: Int32)

Yields the lazy bytestring,

BM\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SO
  


--
Jamie Love
Senior Consultant
Aviarc Australia
Mobile: +61 400 548 048



 

This message has been scanned for viruses and dangerous content 
by MailScanner and is believed to be clean.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bytea decoding

2008-01-20 Thread Bryan Green
Does anyone know of a library that will handle bytea encodings from
postgres?  The bytea field that I need to access contains a jpg file.  I
want to retrieve it from the database and write it out for an image display
program.

bytea:

Bytea octets are also escaped in the output. In general, each
non-printable octet is converted into its equivalent three-digit octal
value and preceded by one backslash. Most printable octets are represented
by their standard representation in the client character set. The octet with
decimal value 92 (backslash) has a special alternative output
representation. Details are in Table
8-8http://www.postgresql.org/docs/7.4/interactive/datatype-binary.html#DATATYPE-BINARY-RESESC.


*Table 8-8. bytea Output Escaped Octets*
Decimal Octet ValueDescriptionEscaped Output Representation ExampleOutput
Result92backslash\\SELECT '\\134'::bytea;\\ 0 to 31 and 127 to 255
non-printable octets\*xxx* (octal value) SELECT '\\001'::bytea;\00132 to
126printable octetsclient character set representation SELECT
'\\176'::bytea;~

Depending on the front end to PostgreSQL you use, you may have additional
work to do in terms of escaping and unescaping bytea strings. For example,
you may also have to escape line feeds and carriage returns if your
interface automatically translates these.

So, here is part of the file from the database:

\377\330\377\340\000\020JFIF\000\001\001\000\000\001\000\001\000\000\377\333\000C\000\012\007\007\010\007\006\012\010\010\010\013\012\012\013\016\030\020\016\015\015\016\035\025\026\021\030#\037%$\037!+7/)4)!0A149;%.DICH7=;\377


I may have to write a converter myself but I don't like re-inventing the
wheel if I don't need to do so.  Any pointers would be greatly appreciated.

Bryan Green
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bug in all about monads tutorial

2008-01-20 Thread Peter Hercek

Hi,

About 3 weeks ago I reported this bug to Jeff Newbern.
 But I got no response - maybe I got filtered out as spam :)
 Since it was not fixed I'm trying once more here. Maybe
 there is somebody here who has access to the web site
 http://www.haskell.org/all_about_monads and cares enough
 to fix it.

On page
 http://www.haskell.org/all_about_monads/html/writermonad.html
there is listens defined like this:
 listens f m = do (a,w) - m; return (a,f w)
... but it should be like this:
 listens f m = do (a,w) - listen m; return (a,f w)
... or maybe a less strict option (as ghc libs have it):
 listens f m = do ~(a,w) - listen m; return (a,f w)

Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Need help with Parsec

2008-01-20 Thread Nicu Ionita
Hi,

I'm playing since a few hours with Parsec and trying to write a small html
(fragment) parser, but I'm stuck in a point which I really can't understand.

The problem seem to be either in parseProperCont or in closing (see code
below). It looks like closing does not work (but it is a very simple
function!) or (also hard to believe) function try from Parsec has some
problems.

Anyway I get this answer:

Prelude ParseSHtml pf parseHtmlFrg ptest.txt
Left ptest.txt (line 5, column 2):
unexpected /
expecting element name

when I'm parsing this file:

div id=normtext
one line with breakbr /
another line br /br /
Mail: a href=mailto:[EMAIL PROTECTED][EMAIL PROTECTED]/a
/div

with this code (sorry for the longer mail):

import Text.ParserCombinators.Parsec hiding (label)
import Text.XHtml.Strict

-- Helper function: parse a string up to one of the given chars
upTo :: [Char] - Parser [Char]
upTo ds = many1 (noneOf ds)

parseHtmlFrg :: Parser Html
parseHtmlFrg = do many space
  choice [parseElem, parseText]
   ? html fragment

parseElem :: Parser Html
parseElem = do en - parseElTag
   many1 space
   (ats, cnt) - restElem en
   return $ compElem en cnt ! ats
? html element

-- Compose a html element from tag name and content
compElem en cnt = if isNoHtml cnt then itag en else tag en cnt

parseElTag :: Parser String
parseElTag = do char ''
en - elemName
return en
 ? element tag

elemName :: Parser String
elemName = many1 lower ? element name

restElem :: String - Parser ([HtmlAttr], Html)
restElem nm = do ats - parseAttList
 ht - (restElNoCont | restElCont nm)
 return (ats, ht)
  ? ( or / to close the tag  ++ nm)

-- Rest element with no content
restElNoCont = do char '/'
  char ''
  return noHtml
   ? /

-- Rest element with content
restElCont nm = do char ''
   many space
   els - parseProperCont nm
   return $ concatHtml els
? element with content

-- Parse closing tag or proper content(s)
parseProperCont :: String - Parser [Html]
parseProperCont nm = try (do closing nm
 return []
  )
 | (do h - parseHtmlFrg
 hs - parseProperCont nm
 return (h:hs)
  )
 -- | return []
 ? proper element content

closing nm = do char ''
char '/'
nm1 - elemName
char ''
if nm1 == nm
   then return ()
   else fail $ nm ++ , encountered  ++ nm1
 ? (closing of  ++ nm)

-- Parse a html attribute
parseAttr :: Parser HtmlAttr
parseAttr = do at - many1 lower
   char '='
   va - parseQuote
   many space
   return $ strAttr at va
? Attribut
parseAttList = many1 parseAttr | return [] ? attribute list

-- Parse a quoted string
parseQuote :: Parser String
parseQuote = do char ''
cs - upTo ['']
char ''
return cs

-- Parse a text element
parseText :: Parser Html
parseText = do s - upTo 
   return (stringToHtml s)
? some text

-- For tests:
pf p file = parseFromFile p file

Nicu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type issues for a foldable trie in Haskell

2008-01-20 Thread Brad Larsen

Hello there,

I have written a trie in Haskell generalized to Eq a = [a] rather than  
simply String.  I want to make this type an instance of Foldable, but I've  
run into a type dilemma.  My datatypes look like this:


data TrieElem a = Elem a | Start | End
  deriving (Read, Show, Eq, Ord)

data Trie a = Trie {label :: TrieElem a
   ,children :: [Trie a]}
  deriving (Read, Show, Eq, Ord)

The signature of Data.Foldable.foldr is (Data.Foldable.Foldable t) = (a  
- b - b) - b - t a - b.  However, I want the functions in Foldable to  
operate on the _list type_ that Trie stores rather than the _elements_ of  
that list type---Trie a stores lists of type a.  For example, a Trie  
storing strings would have type Trie Char, and I want Trie Char to be  
Foldable, but where the functions operate on String rather than Char.


So, with the datatype definitions of Trie and TrieElem as they are above,  
to define a fold function that operates the way I want would have  
signature ([a] - b - b) - b - Trie a - b, which is no good for making  
Trie a an instance of Foldable.


Hopefully this doesn't just seem like rambling :-).  How might I rewrite  
my datatypes to do what I want, preferably without using ghc extensions?   
Thanks!


Brad Larsen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need help with Parsec

2008-01-20 Thread Sterling Clover
Here's a handy simple function I've found very useful. You'll  
obviously also need to import Debug.Trace:


pTrace s = pt | return ()
where pt = try $
   do
 x - try $ many1 anyChar
 trace (s++:  ++x) $ try $ char 'z'
 fail x

It could perhaps be cleaner, but it does the job for me fine. Just  
insert a line like pTrace label anywhere in your parsing functions  
and whenever parsec hits that line you get a nice line of output:  
label: rest of string to be parsed This tends to help track down  
just where your code goes wrong. Try works like it should in my  
experience, but that doesn't necessarily mean it works how you expect.


Regards,
s

On Jan 20, 2008, at 12:12 PM, Nicu Ionita wrote:


Hi,

I'm playing since a few hours with Parsec and trying to write a  
small html
(fragment) parser, but I'm stuck in a point which I really can't  
understand.


The problem seem to be either in parseProperCont or in  
closing (see code

below). It looks like closing does not work (but it is a very simple
function!) or (also hard to believe) function try from Parsec has  
some

problems.

Anyway I get this answer:

Prelude ParseSHtml pf parseHtmlFrg ptest.txt
Left ptest.txt (line 5, column 2):
unexpected /
expecting element name

when I'm parsing this file:

div id=normtext
one line with breakbr /
another line br /br /
Mail: a href=mailto:[EMAIL PROTECTED][EMAIL PROTECTED]/a
/div

with this code (sorry for the longer mail):

import Text.ParserCombinators.Parsec hiding (label)
import Text.XHtml.Strict

-- Helper function: parse a string up to one of the given chars
upTo :: [Char] - Parser [Char]
upTo ds = many1 (noneOf ds)

parseHtmlFrg :: Parser Html
parseHtmlFrg = do many space
  choice [parseElem, parseText]
   ? html fragment

parseElem :: Parser Html
parseElem = do en - parseElTag
   many1 space
   (ats, cnt) - restElem en
   return $ compElem en cnt ! ats
? html element

-- Compose a html element from tag name and content
compElem en cnt = if isNoHtml cnt then itag en else tag en cnt

parseElTag :: Parser String
parseElTag = do char ''
en - elemName
return en
 ? element tag

elemName :: Parser String
elemName = many1 lower ? element name

restElem :: String - Parser ([HtmlAttr], Html)
restElem nm = do ats - parseAttList
 ht - (restElNoCont | restElCont nm)
 return (ats, ht)
  ? ( or / to close the tag  ++ nm)

-- Rest element with no content
restElNoCont = do char '/'
  char ''
  return noHtml
   ? /

-- Rest element with content
restElCont nm = do char ''
   many space
   els - parseProperCont nm
   return $ concatHtml els
? element with content

-- Parse closing tag or proper content(s)
parseProperCont :: String - Parser [Html]
parseProperCont nm = try (do closing nm
 return []
  )
 | (do h - parseHtmlFrg
 hs - parseProperCont nm
 return (h:hs)
  )
 -- | return []
 ? proper element content

closing nm = do char ''
char '/'
nm1 - elemName
char ''
if nm1 == nm
   then return ()
   else fail $ nm ++ , encountered  ++ nm1
 ? (closing of  ++ nm)

-- Parse a html attribute
parseAttr :: Parser HtmlAttr
parseAttr = do at - many1 lower
   char '='
   va - parseQuote
   many space
   return $ strAttr at va
? Attribut
parseAttList = many1 parseAttr | return [] ? attribute list

-- Parse a quoted string
parseQuote :: Parser String
parseQuote = do char ''
cs - upTo ['']
char ''
return cs

-- Parse a text element
parseText :: Parser Html
parseText = do s - upTo 
   return (stringToHtml s)
? some text

-- For tests:
pf p file = parseFromFile p file

Nicu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hangman game

2008-01-20 Thread Paul Johnson

Ronald Guida wrote:

Hi,

I'm interested in learning how to program games.  Since I have to start
somewhere, I decided to write a simple Hangman game.  I'm wondering if
anyone can look at my code and give me some feedback.
Nicely written.  The design reads very much like a straight translation 
from the imperative style, which is why so much of it is in the IO 
monad.  There is nothing wrong with this for a simple game like Hangman, 
but for larger games it doesn't scale.  So here are a few pointers to 
ways of rewriting it to keep the IO to the top level and the actual work 
in a functional style:


1: Your GameState type can itself be made into a monad.  Take a look at 
the All About Monads tutorial, especially the State monad.  Think 
about the invariants in GameState; can you produce a new monad that 
guarantees these invariants through a limited set of actions.  How do 
these actions correspond to user perceptions?


2: You can layer monads by using monad transformers.  Extend the 
solution to part 1 by using StateT IO instead of just State.


3: Your current design uses a random number generator in the IO monad.   
Someone already suggested moving that into the GameState.  But you can 
also generate an infinite list of random numbers.  Can you make your 
game a function of a list of random numbers?


4: User input can also be considered as a list.  Haskell has lazy 
input, meaning that you can treat user input as a list that actually 
only gets read as it is required.  Can you make your game a function of 
the list of user inputs?  How does this interact with the need to 
present output to the user?  What about the random numbers?


Good luck,

Paul.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bytea decoding

2008-01-20 Thread Adam Langley
2008/1/20 Bryan Green [EMAIL PROTECTED]:
 Does anyone know of a library that will handle bytea encodings from
 postgres?  The bytea field that I need to access contains a jpg file.  I
 want to retrieve it from the database and write it out for an image display
 program.

I'd love to see Don give the correct ByteString solution, but here's a
slow version I knocked up (probably buggy):

import qualified Data.ByteString as B
import Data.ByteString.Internal (c2w)
import Data.Maybe (catMaybes)
import Data.List (mapAccumL)

byteaDecode :: B.ByteString - B.ByteString
byteaDecode = B.pack . catMaybes . snd . mapAccumL f initState . B.unpack where
  initState = (0, 0)
  f (0, _) 92 = ((1, 0), Nothing)
  f (0, _) x = ((0, 0), Just x)
  f (1, _) 92 = ((0, 0), Just 92)
  f (3, n) x = ((0, 0), Just (n * 8 + (x - 48)))
  f (c, n) x = ((c + 1, n * 8 + (x - 48)), Nothing)


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Data.Binary questions

2008-01-20 Thread Lauri Pesonen
Hi,

I'm relatively new to Haskell so please bear with me. I'm trying to
parse Java class files with Data.Binary and I'm having a few problems:

(The class file format is described here:
http://java.sun.com/docs/books/jvms/second_edition/html/ClassFile.doc.html
and the bytecode instructions are described here:
http://java.sun.com/docs/books/jvms/second_edition/html/Instructions.doc.html
)

1. The class file format contains a number of tables. The table
definitions start with the length of the list and carry on with that
many table entries. Lists would be a good representation for them in
Haskell, because  there is not need to index them directly (except
with the constants table). I've created my own list type so that I can
redefine the serialisation functions for it so that the serialisation
matches the format defined in the class file format:

newtype MyList e = MkList ([e])
deriving Show

instance (Binary e) = Binary (MyList e) where
 put (MkList es) = do
   put (fromIntegral (length es) :: Word16)
   mapM_ put es

 get = do
 n - get :: Get Word16
 xs - replicateM (fromIntegral n) get
 return (MkList xs)

The problem is that one of the tables, namely the attribute_info
structures, use a u32 length field whereas all the other tables use a
u16 length field. My implementation uses u16, but it would be nice to
be able to use the same data type for both types of tables. I think I
can do it by adding a lenght field to MyList and specifying the type
when I use MyList in some other data structure, but that would also
mean that I have to keep track of the length of the list manually?

I'm basically copy-pasting the same code just to use a u32 length
field in the serialised form:

data Info = MkInfo [Word8]
 deriving Show

instance Binary Info where
 put (MkInfo xs) = do
  put (fromIntegral (length xs) :: Word32)
  mapM_ put xs

 get = do
 n - get :: Get Word32
 xs - replicateM (fromIntegral n) get
 return (MkInfo xs)


2. This is the bigger problem. The Java class file contains a
constants table in the beginning of the file. The other fields later
on in the class file contain indexes that reference entries in that
constants table. So in order to be able to replace an index in a data
structure with the actual string, I need to be able to look up the
string from the constants table while I'm deserialising the field.

My guess is that I should be able to put the constants table into a
state monad. On the other hand Data.Binary already uses the state
monad for holding onto the binary data being deserialised. So it's not
clear to me if I can use StateT with Data.Binary.Get? And if not, can
I implement my own state monad and do it that way? I'm not very
comfortable with Monads yet, so I might be missing something very
obvious.

This is what the get function looks like in my top-level Data.Binary instance:

 get = do magic - get :: Get Word32
  case magic == magicNumber of -- class files start
with 0xCAFEBABE
   True - do min - get -- minor version number u16
  maj - get -- major version number u16
  c - get -- constants table
  a - get -- access flags (public,
abstract, ...) u16
  t - get -- a u16 index pointing to
the name of this class in the constants table
  s - get -- a u16 index pointing to
the name of the super class in the constants table
  i - get -- a table of interfaces
  f - get -- a table of fields
  m - get -- a table of methods
  attrs - get -- a table of class
level attributes
  return (ClassFile (min, maj) c a t s
i f m attrs)
   False - error Invalid magic number

Thanks for all the help!

-- 
  ! Lauri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Binary questions

2008-01-20 Thread Derek Elkins
On Sun, 2008-01-20 at 18:18 +, Lauri Pesonen wrote:
 Hi,
 
 I'm relatively new to Haskell so please bear with me. I'm trying to
 parse Java class files with Data.Binary and I'm having a few problems:
 
 (The class file format is described here:
 http://java.sun.com/docs/books/jvms/second_edition/html/ClassFile.doc.html
 and the bytecode instructions are described here:
 http://java.sun.com/docs/books/jvms/second_edition/html/Instructions.doc.html
 )
 
 1. The class file format contains a number of tables. The table
 definitions start with the length of the list and carry on with that
 many table entries. Lists would be a good representation for them in
 Haskell, because  there is not need to index them directly (except
 with the constants table). I've created my own list type so that I can
 redefine the serialisation functions for it so that the serialisation
 matches the format defined in the class file format:
 
 newtype MyList e = MkList ([e])
 deriving Show
 
 instance (Binary e) = Binary (MyList e) where
  put (MkList es) = do
put (fromIntegral (length es) :: Word16)
mapM_ put es
 
  get = do
  n - get :: Get Word16
  xs - replicateM (fromIntegral n) get
  return (MkList xs)
 
 The problem is that one of the tables, namely the attribute_info
 structures, use a u32 length field whereas all the other tables use a
 u16 length field. My implementation uses u16, but it would be nice to
 be able to use the same data type for both types of tables. I think I
 can do it by adding a lenght field to MyList and specifying the type
 when I use MyList in some other data structure, but that would also
 mean that I have to keep track of the length of the list manually?

You may want to consider using the other side of Data.Binary rather than
the Binary class.  The -class- Binary is intended for de/serialization
when you don't care about the format.  From the documentation:

For parsing and generating simple external binary formats (e.g. C
structures), Binary may be used, but in general is not suitable for
complex protocols. Instead use the Put and Get primitives directly.

Nevertheless, one way to solve your problem is with a phantom type.
Change MyList to,
newtype MyList t e = MkList [e] deriving Show

getLengthType :: MyList t e - t
getLengthType = undefined

instance (Binary e) = Binary (MyList t e) where
 put l@(MkList es) = do
 put (fromIntegral (length es) `asTypeOf` getLengthType l)
 mapM_ put es

 get = do
 n - get
 xs - replicateM (fromIntegral (n `asTypeOf` getLengthType t)) get
 return (MkList xs `asTypeOf` t)
   where t = undefined

The asTypeOfs are just to propagate the type information around.  GHC's
extension for scoped type variables would make this code simpler and
more direct.  At any rate, now the code will use the Binary instance for
whatever type t is to serialize the length.

 2. This is the bigger problem. The Java class file contains a
 constants table in the beginning of the file. The other fields later
 on in the class file contain indexes that reference entries in that
 constants table. So in order to be able to replace an index in a data
 structure with the actual string, I need to be able to look up the
 string from the constants table while I'm deserialising the field.
 
 My guess is that I should be able to put the constants table into a
 state monad. On the other hand Data.Binary already uses the state
 monad for holding onto the binary data being deserialised. So it's not
 clear to me if I can use StateT with Data.Binary.Get? And if not, can
 I implement my own state monad and do it that way? I'm not very
 comfortable with Monads yet, so I might be missing something very
 obvious.

If you mean that you there references to the constant table in e.g. the
fields table then the problem here is that you need to the class methods
to use that monad transformer (in this case, ReaderT is all you should
need and not even that), but you can't change their type.  These are the
kind of issues that make the Binary class unsuitable for this type of
work.  If that is the case, the only way to use this is to explicitly
write out the deserialization code rather than relying on get, i.e.
you'll have to write a function 'getTable constantTable' that will
deserialize the table.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] CPP and INLINE pragmas

2008-01-20 Thread Adam Langley
Since CPP mode removes newlines in the out macro expansion. It appears
to be impossible to have a macro expand to a function with an INLINE
pragma since it appears to need to be in its own line.

For example:

#define GETHOSTWORD(name, m, type) \
{-# INLINE name #-} \
name :: m type ; \
name = getPtr (sizeOf (undefined :: type)) \

Does work (since you can't follow the INLINE pragma with anything else
on the same line.

Likewise:

#define GETHOSTWORD(name, m, type) \
name :: m type ; \
name = getPtr (sizeOf (undefined :: type)) \
{-# INLINE name #-}

Also doesn't work since the INLINE needs to start at the beginning of a line.

Has anyone a workaround for this, or a way to get the preprocessor to
output a newline?


Cheers

AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hangman game

2008-01-20 Thread Yitzchak Gale
Hi Paul,

You gave some suggestions of other styles of Haskell programming
that Ronald could try for his program. These styles are definitely
worth knowing, so if Ronald is not familiar with them, he may want
to try them out. However, in most cases, I think what Ronald
already did is nicer than what you are suggesting.

Paul Johnson wrote:
 The design reads very much like a straight translation
 from the imperative style, which is why so much of it is in the IO
 monad.  There is nothing wrong with this for a simple game like Hangman,
 but for larger games it doesn't scale.

It's a state monad, and most of his code is in that style. It doesn't
read to me like imperative style at all. And it scales beautifully.

There is a lot of liftIO, because that is the bulk of the work in
this program. But Ronald cleanly separated out the game logic,
and even the pure parts of the UI logic, into pure functions
like handleGuess and renderGameState. I personally might
have kept a more consistently monadic style by writing those
as pure monads, like:

handleGuess :: MonadState GameState m = Char - m ()
renderGameState :: MonadState GameState m - m String

In certain situations, that approach gives more flexiblity.
Like for refactoring, or adding new features. But Ronald's
approach is also very nice, and I might also do that.

 1: Your GameState type can itself be made into a monad.

Yes, it can. But StateT GameState IO is the perfect
monad for this game - writing a new monad would just be
reinventing the wheel. It would certainly be a good learning
experience for understanding the inner workings of the
state monad transformer, though.

 2: You can layer monads by using monad transformers.  Extend the
 solution to part 1 by using StateT IO instead of just State.

I think he is already using that type.

 3: Your current design uses a random number generator in the IO monad.
 Someone already suggested moving that into the GameState.  But you can
 also generate an infinite list of random numbers.  Can you make your
 game a function of a list of random numbers?

He could, but I would advise against that technique. In more
complex games, you may need to do many different kinds of
random calculations in complex orders. Keeping a random generator
inside a state monad is perfect for that. And since Ronald already
set up the plumbing for the state monad, he is already home.

Generating an infinite list from a random generator burns up
the generator, making it unusable for any further calculations.
Sometimes that doesn't matter, but I think it's a bad habit. I admit
you'll catch me doing it sometimes though, in quick and dirty
situations like at the GHCi prompt.

 4: User input can also be considered as a list.  Haskell has lazy
 input, meaning that you can treat user input as a list that actually
 only gets read as it is required.  Can you make your game a function of
 the list of user inputs?  How does this interact with the need to
 present output to the user?  What about the random numbers?

That type of lazy IO is considered by many to be one of Haskell's
few warts. It is a hole in the type system that lets a small amount of
side-effects leak through, and even that small amount leads to bugs.

In many situations it's hard to avoid without making a wreck out
of your whole program structure (though more and more tools
are becoming available to help, such as the ByteString stuff).
Ronald did great without it - why resort to that?

All that said - this is clearly a matter of taste, of course.
Thanks for bringing up a variety of approaches.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: A triple of new packages for talking tothe outside world

2008-01-20 Thread Adam Langley
On Jan 15, 2008 7:33 PM, Adam Langley [EMAIL PROTECTED] wrote:
 Ok, no TH ;)

I've just uploaded binary-strict 0.2.2 to Hackage which factors most
of the common code out via CPP. Hopefully I didn't break anything.



AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread Jon Harrop
On Sunday 20 January 2008 21:02:04 [EMAIL PROTECTED] wrote:
 On 2008.01.19 19:11:13 +0100, Peter Verswyvelen [EMAIL PROTECTED] scribbled 
1.4K characters:
  I would find it most useful to get type inference information on the fly,
  even when not all of the code compiles correctly yet.

 Does that make sense? If the code doesn't compile, then how could any
 type-inference be trustable?

Note that this functionality continues to be widely used in other functional 
languages, e.g. SML, OCaml, F#. I can't think why Haskell would be any 
different.

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
http://www.ffconsultancy.com/products/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec benchmarks

2008-01-20 Thread Jon Harrop

I'd like to compare the performance of Parsec to other parsers but the only 
reference to a benchmark I have found is a dead link from one of the papers 
about Parsec:

  http://research.microsoft.com/users/daan/download/parsec/parsec.pdf

Are there any surviving Parsec benchmarks?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
http://www.ffconsultancy.com/products/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread gwern0
On 2008.01.19 19:11:13 +0100, Peter Verswyvelen [EMAIL PROTECTED] scribbled 
1.4K characters:
 The problem is that this only works when the complete source file compiles
 correctly no?

Yes. As I said, it's a very hackish solution - think of it as proof-of-concept.

 I would find it most useful to get type inference information on the fly,
 even when not all of the code compiles correctly yet.

Does that make sense? If the code doesn't compile, then how could any 
type-inference be trustable? It might be reliable if the error is in 
definitions which don't get called or otherwise used by the function you are 
asking after, but there are going to be edge-cases, I should think, where it 
would bite you.

--
gwern
Freeh ASU 32 CIO GGL Force 97 b in Macintosh


pgpjicjhzpFeX.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec benchmarks

2008-01-20 Thread Johan Tibell
On Jan 20, 2008 9:54 PM, Jon Harrop [EMAIL PROTECTED] wrote:

 I'd like to compare the performance of Parsec to other parsers but the only
 reference to a benchmark I have found is a dead link from one of the papers
 about Parsec:

   http://research.microsoft.com/users/daan/download/parsec/parsec.pdf

 Are there any surviving Parsec benchmarks?

I'm very interested in a common benchmark which I could try my
ByteString implementation of Parsec against.

-- Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Throwback of inferred types

2008-01-20 Thread Achim Schneider
[EMAIL PROTECTED] wrote:

 Does that make sense? If the code doesn't compile, then how could any
 type-inference be trustable? 

Why, of course it is trustable, because it's going to fail, and that
means that the code has type a - _|_.


-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread Jon Harrop
On Sunday 20 January 2008 22:06:04 Duncan Coutts wrote:
 On Sun, 2008-01-20 at 21:02 +, Jon Harrop wrote:
  On Sunday 20 January 2008 21:02:04 [EMAIL PROTECTED] wrote:
   On 2008.01.19 19:11:13 +0100, Peter Verswyvelen [EMAIL PROTECTED]
   scribbled
 
  1.4K characters:
I would find it most useful to get type inference information on the
fly, even when not all of the code compiles correctly yet.
  
   Does that make sense? If the code doesn't compile, then how could any
   type-inference be trustable?
 
  Note that this functionality continues to be widely used in other
  functional languages, e.g. SML, OCaml, F#. I can't think why Haskell
  would be any different.

 Really? That's pretty cool. How does it work?

With OCaml you compile with the -dtypes option and inferred types are 
available in the IDE. For example, in Emacs you hit C+C C+T to get the type 
of the subexpression under the cursor. In OCaIDE, this is provided as 
graphical throwback of the subexpression under the mouse in Eclipse and 
repeat type checking passes are automated.

In F#, the Visual Studio mode provides the same functionality.

I believe MLton provides the same functionality for SML.

 Does it use Achim's suggestion of replacing expressions which fail to
 type with new type vars and at runtime an error message with the type
 error?

I believe it just dumps the types of all subexpressions to file with source 
code locations as they are inferred. In the case of broken code, the given 
type is either non-existant (nothing is given because nothing has been 
inferred), more general that it should be (because later unifications have 
not yet been made) or wrong (which is most valuable when debugging type 
errors).

 Or do they use something more hacky that we could also implement 
 quickly?

OCaml generates .annot files that look like this:

nth.ml 6 68 78 nth.ml 6 68 91
type(
  string - int Gram.Entry.t
)
nth.ml 6 68 92 nth.ml 6 68 97
type(
  int Gram.Entry.t
)
nth.ml 6 68 92 nth.ml 6 68 97
type(
  string
)
nth.ml 6 68 72 nth.ml 6 68 97
type(
  int Gram.Entry.t
)

 That would be cool. Then I can run the bits of my program that still
 work. It'd make the editor/interpreter session rather more live.

Exactly.

 How close do the IDEs/emacs-modes for SML, OCaml, F# come to that? What
 are we missing out on? :-)

You're missing out on a lot if this isn't available for Haskell yet. I didn't 
realise just how invaluable this is until a system upgrade broke it and I 
really struggled to write OCaml code without it: I don't know how I managed 
before!

Some people argue that functional programming languages don't need decent 
development environments but, having used F#, I know better...

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
http://www.ffconsultancy.com/products/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread Duncan Coutts

On Sun, 2008-01-20 at 21:02 +, Jon Harrop wrote:
 On Sunday 20 January 2008 21:02:04 [EMAIL PROTECTED] wrote:
  On 2008.01.19 19:11:13 +0100, Peter Verswyvelen [EMAIL PROTECTED] 
  scribbled 
 1.4K characters:
   I would find it most useful to get type inference information on the fly,
   even when not all of the code compiles correctly yet.
 
  Does that make sense? If the code doesn't compile, then how could any
  type-inference be trustable?
 
 Note that this functionality continues to be widely used in other functional 
 languages, e.g. SML, OCaml, F#. I can't think why Haskell would be any 
 different.

Really? That's pretty cool. How does it work?

Does it use Achim's suggestion of replacing expressions which fail to
type with new type vars and at runtime an error message with the type
error? Or do they use something more hacky that we could also implement
quickly?

like:

foo = 3

bar = 'c'

baz = foo + bar


So we infer:

foo :: Int
foo = 3

bar :: Char
bar = 'c'

baz :: a
baz = error No instance for (Num Char)
 arising from a use of `+' at foo.hs:5:6-14

That would be cool. Then I can run the bits of my program that still
work. It'd make the editor/interpreter session rather more live. 

How close do the IDEs/emacs-modes for SML, OCaml, F# come to that? What
are we missing out on? :-)

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPP and INLINE pragmas

2008-01-20 Thread Isaac Dupree

Adam Langley wrote:

Since CPP mode removes newlines in the out macro expansion. It appears
to be impossible to have a macro expand to a function with an INLINE
pragma since it appears to need to be in its own line.


that's because INLINE uses layout like everything else, so you can use 
semicolons for it too.



For example:

#define GETHOSTWORD(name, m, type) \
{-# INLINE name #-} \
name :: m type ; \
name = getPtr (sizeOf (undefined :: type)) \



something like

#define GETHOSTWORD(name, m, type) \
{-# INLINE name #-} ; \
name :: m type ; \
name = getPtr (sizeOf (undefined :: type)) \


~Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Throwback of inferred types

2008-01-20 Thread Jonathan Cast

On 20 Jan 2008, at 1:02 PM, [EMAIL PROTECTED] wrote:

On 2008.01.19 19:11:13 +0100, Peter Verswyvelen [EMAIL PROTECTED]  
scribbled 1.4K characters:
The problem is that this only works when the complete source file  
compiles

correctly no?


Yes. As I said, it's a very hackish solution - think of it as proof- 
of-concept.


I would find it most useful to get type inference information on  
the fly,

even when not all of the code compiles correctly yet.


Does that make sense? If the code doesn't compile, then how could  
any type-inference be trustable? It might be reliable if the error  
is in definitions which don't get called or otherwise used by the  
function you are asking after, but there are going to be edge- 
cases, I should think, where it would bite you.


Even if it's not reliable, the compiler gives its error messages  
based on some form of partial type inference.  It would be quite  
interesting, some times, to see what the compiler thinks the types  
are, when it gives a type error (this bit me recently trying  
polymorphic recursion: I had a long list of polymorphic functions  
defined without type signatures (since the names were clear enough),  
factored out some duplicated code, and wound up with a set of  
mutually recursive functions, one of which was polymorphically  
recursive.  I'll dig the example up if you want (it's kind of  
compilcated).  Knowing that the compiler had various types inferred  
correctly would have helped me zero in on the place I needed a type  
signature (or at least I remember wanting to find such things out at  
the time)).


jcc

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPP and INLINE pragmas

2008-01-20 Thread Malcolm Wallace
Adam Langley [EMAIL PROTECTED] writes:

 Has anyone a workaround for this, or a way to get the preprocessor to
 output a newline?

You can use cpphs with the --layout flag, to preserve newlines in macro
expansion.
http://haskell.org/cpphs

For instance, with ghc you need to add the following flags:

ghc -cpp -pgmPcpphs -optP--cpp -optP--layout

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CPP and INLINE pragmas

2008-01-20 Thread Adam Langley
Thanks Isaac and Malcolm. That neatly solves all my problems!


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-20 Thread Steve Lihn
This fixed the second example. Thanks.


 I think handleConnection should be

 handleConnection :: RequestHandler - Handle - IO ()

 handleConnection r h =
  handleToRequest h = responseSend h . runRequestHandler r


 Levi



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bug in all about monads tutorial

2008-01-20 Thread Benjamin L. Russell
Since nobody with write access to that page seems to
be responding here, you may wish to try reporting this
bug to the main Haskell mailing list
([EMAIL PROTECTED]).

Posting to that list may get the attention of some
Haskell users who may not regularly read this mailing
list.

Benjamin L. Russell

--- Peter Hercek [EMAIL PROTECTED] wrote:

 Hi,
 
 About 3 weeks ago I reported this bug to Jeff
 Newbern.
   But I got no response - maybe I got filtered out
 as spam :)
   Since it was not fixed I'm trying once more here.
 Maybe
   there is somebody here who has access to the web
 site
   http://www.haskell.org/all_about_monads and cares
 enough
   to fix it.
 
 On page
  

http://www.haskell.org/all_about_monads/html/writermonad.html
 there is listens defined like this:
   listens f m = do (a,w) - m; return (a,f w)
 ... but it should be like this:
   listens f m = do (a,w) - listen m; return (a,f w)
 ... or maybe a less strict option (as ghc libs have
 it):
   listens f m = do ~(a,w) - listen m; return (a,f
 w)
 
 Peter.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Invitation for MathematiKa '08 : projectEuler format

2008-01-20 Thread anshuman
Hello Math Enthusiast,

IIIT-Hyderabad, India cordially invites you to be a part of Mathematika
'08, an online competition that emphasizes on fusion of mathematics and
computing.

Where: http://felicity.iiit.ac.in/~math
When: 4th February, 2008

This Online Math Contest will consist of 10-12 problems made randomly from
different domains of existing Math. All problem statements will be visible
to the contestant from the start of contest spanning over a 10 hour
period. The solution to each problem would be an integer or a floating
point number which is to be submitted in real-time.

One Minute Rule: The problems are designed in a way that support 1 minute
rule which means that an efficient implementation will allow a solution to
be obtained on a modestly powered computer in less than one minute.

Also, make sure to bring your appetite for math, programming and fun.
There will be plenty of all three to go around.

Regards
Mathematika Team
http://felicity.iiit.ac.in/~math


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe