Re: [Haskell-cafe] multiline strings in haskell?

2006-01-12 Thread Henning Thielemann

On Wed, 11 Jan 2006, Michael Vanier wrote:

 Is there any support for multi-line string literals in Haskell?  I've
 done a web search and come up empty.  I'm thinking of using Haskell to
 generate web pages and having multi-line strings would be very useful.

Do you mean

unlines [first line, second line, third line]

?

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


Re[2]: [Haskell-cafe] I/O and utf8

2006-01-12 Thread Bulat Ziganshin
Hello Einar,

Wednesday, January 11, 2006, 6:14:44 PM, you wrote:

EK Do you plan on supporting things like HTTP where the character set
EK is only known in the middle of the parsing?

yes, it is supported, see Examples/Encoding.hs in the
http://freearc.narod.ru/Binary.tar.gz :

 h - openWithEncoding latin1 = openBinaryFile test ReadMode
 print = vGetLine h
 vSetEncoding h utf8
 print = vGetLine h
 vSetEncoding h latin1
 print = vGetLine h
 vClose h

it's not optimized currently. if you will need more speed - yell me


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: Shootout favoring imperative code

2006-01-12 Thread Bulat Ziganshin
Hello Einar,

Wednesday, January 11, 2006, 6:06:56 PM, you wrote:

 My version of the packed string library does have an hGetLine.  Don
 Stewart was merging my version with his fps at some point, Don - any 
 news on that?

EK Getting a fast FastPackedString will solve the problems with many
EK benchmarks.

btw, JHC's version of FPS uses slightly less memory (i don't remember,
8 or 12 bytes per each string) and i think must be faster (because it
uses ByteArray# instead of Addr#). so, the best variant is to add hGetLine
to John's library

   set arr x yv

(arr,x) =: yv

looks better ;)

EK and so forth. Usually imperative solutions have something like
EK a[i] += b[i], which currently is quite tedious and ugly to
EK translate to MArrays. Now it would become combineTo a i (+) b i.

you are definitely a Hal Daume's client, look at 
http://www.isi.edu/~hdaume/STPP/


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] multiline strings in haskell?

2006-01-12 Thread Jason Dagit


On Jan 12, 2006, at 1:34 AM, Henning Thielemann wrote:



On Wed, 11 Jan 2006, Michael Vanier wrote:


Is there any support for multi-line string literals in Haskell?  I've
done a web search and come up empty.  I'm thinking of using  
Haskell to
generate web pages and having multi-line strings would be very  
useful.


Do you mean

unlines [first line, second line, third line]


The original poster probably meant something like this:

let foo = This is a
long string


Which does not end until the matching end quote.

Common Lisp has strings like this.  Quite convenient whenever you're  
communicating using lots of strings of data.  For example, when  
running as a cgi script.


Thanks,
Jason

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


Re: [Haskell-cafe] multiline strings in haskell?

2006-01-12 Thread Henning Thielemann

On Thu, 12 Jan 2006, Jason Dagit wrote:

 On Jan 12, 2006, at 1:34 AM, Henning Thielemann wrote:

  On Wed, 11 Jan 2006, Michael Vanier wrote:
 
  Is there any support for multi-line string literals in Haskell?  I've
  done a web search and come up empty.  I'm thinking of using
  Haskell to
  generate web pages and having multi-line strings would be very
  useful.
 
  Do you mean
 
  unlines [first line, second line, third line]

 The original poster probably meant something like this:

 let foo = This is a
 long string


 Which does not end until the matching end quote.

I don't see the need for it, since

unlines [
  first line,
  second line,
  third line]

works as well.

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


Re: [Haskell-cafe] multiline strings in haskell?

2006-01-12 Thread Sebastian Sylvan
On 1/12/06, Henning Thielemann [EMAIL PROTECTED] wrote:

 On Thu, 12 Jan 2006, Jason Dagit wrote:

  On Jan 12, 2006, at 1:34 AM, Henning Thielemann wrote:
 
   On Wed, 11 Jan 2006, Michael Vanier wrote:
  
   Is there any support for multi-line string literals in Haskell?  I've
   done a web search and come up empty.  I'm thinking of using
   Haskell to
   generate web pages and having multi-line strings would be very
   useful.
  
   Do you mean
  
   unlines [first line, second line, third line]
 
  The original poster probably meant something like this:
 
  let foo = This is a
  long string
 
 
  Which does not end until the matching end quote.

 I don't see the need for it, since

 unlines [
   first line,
   second line,
   third line]

 works as well.


Nevertheless Haskell supports multiline strings (although it seems
like a lot of people don't know about it). You escape it using \ and
then another \ where the string starts again.

str = multi\
\line

Preludestr
multiline


/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Chameneos

2006-01-12 Thread Isaac Gouy
--- Aaron Denney [EMAIL PROTECTED] wrote:

Are we off-topic for this mailing-list? 
I'd just like to respond to this:

 Anyways, your shootout, your hard work, your rules,
 but having rulings on what's acceptable be easier to
 find would be nice.

People here have made the effort to develop programs
for the shootout - I appreciate /their/ hard work.

 

__
Do You Yahoo!?
Tired of spam?  Yahoo! Mail has the best spam protection around 
http://mail.yahoo.com 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What does the Haskell type system do with show (1+2)?

2006-01-12 Thread Jeff . Harper

What does the Haskell type system do
with expressions such as these . . . ?
 show 1
 show (1+2)

The type of the subexpressions 1
and 1+2 are ambiguous since they have type (Num
a) = a. I'm under the assumption before 1+2
is evaluated, the 1 and 2 must be coerced into
a concrete type such as Int, Integer, Double, etc, and before
show 1 is evaluated, the 1 must be coerced into
a concrete type. Is my assumption correct? If so,
how does Haskell know into which type to coerce the subexpressions?

If I try to write a new function, my_show,
which converts an _expression_ into a string representation that includes
type information, I run into errors with expressions like show 1
and show (1+2) because of the type ambiguity.

class (Show a) = My_show a where
 my_show :: a - String

instance My_show Int where
 my_show a = show a ++ 
:: Int

instance My_show Integer where
 my_show a = show a ++ 
:: Integer

I can avoid the errors if I change it
to my_show (1::Int) or my_show ((1+2)::Int). I'm
wondering what the difference is between, my_show and Haskell's built-in
show that causes my_show to produce an error message when it is used with
ambiguous types, but Haskell's show works okay with ambiguous types.



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


Re: [Haskell-cafe] What does the Haskell type system do with show (1+2)?

2006-01-12 Thread Jared Updike
http://www.haskell.org/onlinereport/decls.html#default-decls
http://www.haskell.org/tutorial/numbers.html#sect10.4

On 1/12/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

 What does the Haskell type system do with expressions such as these . . . ?
show 1
show (1+2)

 The type of the subexpressions 1 and 1+2 are ambiguous since they have
 type (Num a) = a.  I'm under the assumption before 1+2 is evaluated,
 the 1 and 2 must be coerced into a concrete type such as Int, Integer,
 Double, etc, and before show 1 is evaluated, the 1 must be coerced into
 a concrete type.  Is my assumption correct?  If so, how does Haskell know
 into which type to coerce the subexpressions?

 If I try to write a new function, my_show, which converts an expression
 into a string representation that includes type information, I run into
 errors with expressions like show 1 and show (1+2) because of the type
 ambiguity.

 class (Show a) = My_show a where
my_show :: a - String

 instance My_show Int where
my_show a = show a ++  :: Int

 instance My_show Integer where
my_show a = show a ++  :: Integer

 I can avoid the errors if I change it to my_show (1::Int) or my_show
 ((1+2)::Int).  I'm wondering what the difference is between, my_show and
 Haskell's built-in show that causes my_show to produce an error message when
 it is used with ambiguous types, but Haskell's show works okay with
 ambiguous types.




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





--
[EMAIL PROTECTED]
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Does anybody have a simple example of using continuation Monad?

2006-01-12 Thread Marc Weber
I'm struggling with this example:
http://www.nomaware.com/monads/html/contmonad.html#example
After looking at it for the fourth time I got much more.. but still not
enough..

because there are so much new things (when beeing translated into some
kind of 
condition ? thentodo : elsetodo
which is using ThenElse  

It wouldn't be any problem if the next example wasn't using
continuation, too.. and that's about combining monads which is
important, isn't it?

At the tutorial there was mentioned that continuation monads are used
for continuation passing style which I've looked up in wikipedia meaning
something like splitting a task into different parts beeing executed
delayed (for example because of user interaction filling a web form?)

I think one simple example like ((+1).(\x-x**2)) in continuation style
would make me understand a lot more..

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


Re: [Haskell-cafe] Does anybody have a simple example of using continuation Monad?

2006-01-12 Thread Cale Gibbard
On 12/01/06, Marc Weber [EMAIL PROTECTED] wrote:
 I'm struggling with this example:
 http://www.nomaware.com/monads/html/contmonad.html#example
 After looking at it for the fourth time I got much more.. but still not
 enough..

 because there are so much new things (when beeing translated into some
 kind of
 condition ? thentodo : elsetodo
 which is using ThenElse  

 It wouldn't be any problem if the next example wasn't using
 continuation, too.. and that's about combining monads which is
 important, isn't it?

 At the tutorial there was mentioned that continuation monads are used
 for continuation passing style which I've looked up in wikipedia meaning
 something like splitting a task into different parts beeing executed
 delayed (for example because of user interaction filling a web form?)

 I think one simple example like ((+1).(\x-x**2)) in continuation style
 would make me understand a lot more..

 Marc


Yeah, that's probably what bothers me most about All About Monads, as
it's otherwise quite a good tutorial. Continuations are a strange
concept, and not exactly the first thing that beginners need to see.
The continuation monad/transformer has its place, but it's rarely
needed, and when abused, it just results in an unreadable mess.

The basic idea about the continuation monad is that the entire
computation you are defining is parametrised on a function which will
take its result and continue to operate on it (the 'future'). The
computation is built up in this way -- at each stage, we extend the
computation by providing another piece of the future, while still
leaving the computation as a whole parametrised on it.

Normally we'd be forced to manage these futures by having explicit
parameters for them and such, but the monad machinery hides all of
this so that you don't have to worry so much about it. If you don't
ever make use of the extra feature that you can get a handle on the
future, you can use it just like the identity monad:

addOne x = return (x+1)
square x = return (x**2)
f x = do y - addOne x; square y

With explicit continuations, this would look something like:

addOne x k = k (x + 1)
square x k = k (x ** 2)
f x k = addOne x (\v - square v k)

Now, this seems like an awkward way to handle things as we're not
making any use of the fact that at each stage, we have a handle to the
future which can be used multiple times, passed into other functions,
etc.

The Cont monad gives one primitive for capturing the current
continuation and passing it into a computation, called callCC.

callCC :: ((a - Cont b) - Cont a) - Cont a

This type requires some study to understand at first, but essentially,
callCC takes a function from a future (a - Cont b) to a new
computation (Cont a), and passes it the current future (which is
accessible due to the funny way in which we're parametrising our
computations).

In terms of callCC, we can write other, more convenient ways to
manipulate futures. The following is due to Tomasz Zielonka [1]:

  getCC :: MonadCont m = m (m a)
  getCC = callCC (\c - let x = c x in return x)

  getCC' :: MonadCont m = a - m (a, a - m b)
  getCC' x0 = callCC (\c - let f x = c (x, f) in return (x0, f))

getCC will get the current continuation explicitly as a computation
which can be executed. This essentially gives us a 'goto-label' at
that point in the computation, and executing it will jump back. This
isn't terribly useful in plain Cont, except to land us in an infinite
loop, but over a state monad, or IO, we can cause side-effect havoc,
observe the state, and decide whether to return to the goto-label or
not.

Stealing an example from Tomasz' original message:

  -- prints hello! in an endless loop
  test :: IO ()
  test = (`runContT` return) $ do
  jump - getCC
  lift $ putStrLn hello!
  jump

getCC' is similar, but actually allows an additional parameter to be
sent back. The parameter to getCC' is just the initial value. Here's a
simplistic implementation of mod by repeated addition/subtraction
which prints intermediate results as it goes, in the ContT transformed
IO monad.

x `modulo` m = (`runContT` return) $ do
(u, jump) - getCC' x
lift $ print u
case u of
  _ | u  0 - jump (u + m)
| u = m- jump (u - m)
| otherwise - return u

 - Cale

[1] http://www.haskell.org/pipermail/haskell-cafe/2005-July/010623.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe