Re: [Haskell-cafe] idea for avoiding temporaries

2007-03-08 Thread Matthias Neubauer
David Roundy [EMAIL PROTECTED] writes:

 I see.  But how would one manage these handles? What's to keep me from
 accidentally copying a handle? It sounds like it'd require explicit memory
 management, in order to avoid ever copying a handle, if I were to implment
 this myself.

Because you seem to write imperative code anyways: can't you simply
use a specialized state monad with the array(s) hidden inside the
monad as monad state?

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] idea for avoiding temporaries

2007-03-08 Thread Matthias Neubauer
David Roundy [EMAIL PROTECTED] writes:

 No, the point is to avoid writing imperative code.  My examples used
 imperative code, but that would be wrapped at the lowest level of the array
 library, and all the real code would be pure.

Still sounds like a state monad to me. Your 'array library', I mean.

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Shootout summary

2006-01-07 Thread Matthias Neubauer
[EMAIL PROTECTED] (Donald Bruce Stewart) writes:

  Fannkuch entry by Bertram Felgenhauer
  Mandelbrot entry
 
 I've done some benchmarking of the current entries for fannkuch and
 mandelbrot, and have proposed final entries for these two tests.

Using = of the list monad in the current Fannkuch proposal
(permutations) hides some costly ++ applications that can be also
optimized away:

Instead of writting
 
  permutations l = foldr perm' [l] [2..length l] 
  where perm' n l = l = take n . iterate (rotate n)
 
saying something like 

  permutations l = foldr perm' [l] [2..length l]

  perm' n  = foldr (takeIter n (rotate n)) []

  takeIter :: Int - (a - a) - a - [a] - [a]
  takeIter 0 f x rest = rest 
  takeIter n f x rest = x : takeIter (n-1) f (f x) rest

gains us another 5% or so.

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Arjan van IJzendoorn [EMAIL PROTECTED] writes:

 Is there a shorter way to write the if-then-else part below?
if (cmdType cmd) /= (CmdSitError Server)
   then return $ Just seat_num
   else return Nothing

 return $ if cmdType cmd /= CmdSitError Serv
   then Just seat_num else Nothing

return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Bulat Ziganshin [EMAIL PROTECTED] writes:

 Hello Matthias,

 Tuesday, November 22, 2005, 9:17:57 PM, you wrote:

 MN return $ guard (cmdType cmd /= CmdSitError Serv)  return seat_num

 return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

 must also work :)

Only if seat_num is of type () ... :-)

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Shortening if-then-else

2005-11-22 Thread Matthias Neubauer
Joel Reymont [EMAIL PROTECTED] writes:

 I don't think it will work for me either way as I'm returning m
 (Maybe Int) where m is my own monad. It seems that folks assumed that
 m itself was the maybe monad. Unless I'm mistaken the code below
 won't work otherwise.

There are two monads involved. The outer return injects into your m
monad. That's all there is for your m.

Then there is the inner stuff. Because the constructor of the inner
expressions, your Maybes, is an instance of MonadPlus, you can use all
the nice stuff there is for MonadPlus.

I'd usually write it like this ...

  return $ do
guard (cmdType cmd /= CmdSitError Serv) 
return seat_num

In case the guard fails, you'll get back mzero (Nothing in your
case).

And then there is also mplus to handle alternatives ...

-Matthias


 On Nov 22, 2005, at 8:50 PM, Tomasz Zielonka wrote:

 On Tue, Nov 22, 2005 at 10:15:15PM +0300, Bulat Ziganshin wrote:

 return $ when (cmdType cmd /= CmdSitError Serv) (return seat_num)

 must also work :)

 But it won't.
 I have made this mistake too in the past ;-)

 --
 http://wagerlabs.com/





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


-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] YAWQ (Yet Another Wash Question)

2005-02-25 Thread Matthias Neubauer
John Goerzen [EMAIL PROTECTED] writes:

 Possible, but ugly.  I have about 50 lines of code that has to go
 in-between, so I'd be duplicating it.  And, if I tried to make it into
 just another function, I'd have the same problem, I believe (scoping)

It's all much easier: as always, you just have to use template
functions for all your pages. That's all you need ... :-)

Here is a recipe how I typically structure my WASH applications:

- First, I write down (html) code for all the web pages and abstract
  over all the varying parts (input fields, submit buttons,
  continuation pages, etc.). As result, I get (independent) template
  function for all the pages. Usually, each template function lives in
  a separate module/file.

- In the end, I write a *controller* function that both generates all
  the different pages by filling the holes of the templates and also
  ties together all the consecutive pages.

And that's all you need to solve your problem as well -- just use a
template function twice! Below, you'll find a small web app that
toggles between two varying input pages using the scheme I described
above.

-Matthias



module Main where

import CGI

main = run controller 

-- controller

controller :: CGI ()
controller = 
  let input1  = tr $ td $ textInputField empty
  submit1 = \ h cont - submit h cont empty
  page1   = stepOneTemplate input1 submit1 page2

  out2= \ t - text t
  submit2 = \ cont - submit0 cont empty
  page2   = stepTwoTemplate value out2 submit2 page3
 
  input3  = empty
  submit3 = \ h cont - submit F0 cont empty
  page3   = stepOneTemplate input3 submit3 page4

  out4= \ t - text No input, sorry!
  submit4 = \ cont - submit0 cont empty
  page4   = stepTwoTemplate (const undefined) out4 submit4 page1
  in page1

-- page templates

stepOneTemplate inputCode submitCode nextPage = do
  standardQuery Input Page $ table $ do
do tr $ td $ text Hello!
   h - inputCode 
   tr $ td $ text Press the button!
   tr $ td $ submitCode h nextPage

stepTwoTemplate validationCode outputCode submitCode nextPage h = do
  let i = validationCode h
  standardQuery Result Page $ table $ do
tr $ td $ text Your input was ...
tr $ td $ outputCode i
tr $ td $ submitCode nextPage



-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] YAWQ (Yet Another Wash Question)

2005-02-25 Thread Matthias Neubauer
John Goerzen [EMAIL PROTECTED] writes:

 On Fri, Feb 25, 2005 at 04:15:55PM +0100, Matthias Neubauer wrote:
   standardQuery Input Page $ table $ do
 do tr $ td $ text Hello!
h - inputCode 
tr $ td $ text Press the button!
tr $ td $ submitCode h nextPage

 I like the idea, but...

 doesn't this still have a problem if inputCode creates multiple fields
 on the screen?  That is, h would only hold the last one?

That's what F0, F1, F2, and friends are for. You use them to wrap
multiple handles into a single object that you then pass to a submit
button.

E.g., my example, now with two buttons on the first step, looks as
follows ...

controller :: CGI ()
controller = 
  let input1  = do h1 - tr $ td $ textInputField empty
   h2 - tr $ td $ textInputField empty
   return (F2 h1 h2)
  submit1 = \ h cont - submit h cont empty
  page1   = stepOneTemplate input1 submit1 page2

  vali2   = \ (F2 h1 h2) - value h1 ++  and  ++ value h2
  out2= \ t - text t
  submit2 = \ cont - submit0 cont empty
  page2   = stepTwoTemplate vali2 out2 submit2 page3
 
  ...

The templates and all the rest stays unchanged.

-Matthias
 




-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] WASH defaults in inputFields

2005-02-23 Thread Matthias Neubauer
John Goerzen [EMAIL PROTECTED] writes:

 I am designing a form that will be used to edit some data that is in the
 database.  I want users to pull up the form and have all the input
 fields pre-filled with the current state of the database (so they don't
 have to re-key all that), then the database gets updated with they hit
 submit.  Simple to do in HTML, but I can't figure out how to do this
 with Wash.  The inputFields don't seem to take a parameter giving a
 default, nor does there appear to be any way to set it later.

 Ideas?

The first argument of input fields is used to attach additional
subnodes to current xml node. I.e., if you pass additional attribute
nodes as first argument, you'll be able to further specify the input
field. There are predefined combinatores (like fieldSIZE or
fieldVALUE) that help to construct common attribute nodes.

Here is a code snippet that should clarify how to do it ...

  ...
  % iName - inputField (fieldSIZE 40 ## fieldMAXLENGTH 40 ## fieldVALUE name 
## attr class name) %
  ...

-Matthias

-- 
Matthias Neubauer   |
Universität Freiburg, Institut für Informatik   | tel +49 761 203 8060
Georges-Köhler-Allee 79, 79110 Freiburg i. Br., Germany | fax +49 761 203 8052
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe