[Haskell-cafe] Re: GUI components for displaying Html pages

2005-02-23 Thread David Owen
Lemmih Wrote:
Is this what you're looking for:
http://wxhaskell.sourceforge.net/doc/Graphics.UI.WXCore.WxcClassesAL.html#88
?
--
Friendly,
  Lemmih
That looks about right.  I hadn't delved that far into WXCore library to 
spot all of those components.  I shall have a go with them.  Thanks!

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


Re: [Haskell-cafe] GUI components for displaying Html pages

2005-02-23 Thread Duncan Coutts
On Wed, 2005-02-23 at 03:25 +, David Owen wrote:
 Hi all,
 
 I'm looking for a Haskell GUI library which supports the display of rendered 
 Html pages in the same way that web browsers do.
 
 I've been getting to grips recently with wxHaskell as it was recommended on 
 haskell-cafe.  I was hoping that a special pane component (or something 
 similar) existed in wxHaskell for the purpose.  I've looked through the API 
 but can't seem to see anything which looks suitable.  Does anybody know if 
 wxHaskell can support this?  If not is anybody aware of a Haskell GUI 
 library which caters for this purpose.

There is also Gtk2Hs which has a binding to the Mozilla rendering engine
embedded in a Gtk+ widget. We have a demo program which shows how to use
it (see demo/mozembed in the source distribution).

http://gtk2hs.sourceforge.net/

and the API reference:
http://gtk2hs.sourceforge.net/docs/gtk2hs-docs-0.9.7/Graphics.UI.Gtk.MozEmbed.html

Duncan

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


[Haskell-cafe] Re: module Crypt_Discordian - code critique requested

2005-02-23 Thread Terrence Brannon
Arthur van Leeuwen [EMAIL PROTECTED] writes:

 On Wed, Feb 23, 2005 at 08:46:23AM +0100, Arthur van Leeuwen wrote:
 On Wed, Feb 23, 2005 at 12:27:19AM +, Terrence Brannon wrote:

 [snip, encryptia discordia]

 How about
 
  module CryptDiscordian
  where
 
  import List
 
  vowels = aeiouAEIOU
  isVowel = (flip elem) vowel_list

you use vowel_list but define vowels

also, I believe isVowel is taking advantage of a curried version of
elem. Correct?

-- 
Carter's Compass: I know I'm on the right track when,
   by deleting something, I'm adding functionality.

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


Re: [Haskell-cafe] module Crypt_Discordian - code critique requested

2005-02-23 Thread David Roundy
On Wed, Feb 23, 2005 at 12:27:19AM +, Terrence Brannon wrote:
 But anyway, here is the algorithm in case you don't enjoy tilting your 
 head to read a page:
 
 Step 1. Write out message (HAIL ERIS) and put all vowels at the end
 (HLRSAIEI) 
 
 Step 2. Reverse order (IEIASRLH)
 
 Step 3. Convert to numbers (9-5-9-1-19-18-12-8)
 
 Step 4. Put into numerical order (1-5-8-9-9-12-18-19)
 
 Step 5. Convert back to letter (AEHIILRS)
 
 This cryptographic cypher code is GUARANTEED TO BE 100% UNBREAKABLE
 
 .. so says the Principia Discordia. But I think we can generate and
 test to break it.

Isn't it guaranteed unbreakable simply because there's no way to decrypt
it? Since there isn't a one-to-one mapping of cyphertext to plaintext, I
don't think it's actually a form of encryption.  Basically it's the same as
the sort function, which is also not invertible.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] module Crypt_Discordian - code critique requested

2005-02-23 Thread Henning Thielemann

On Wed, 23 Feb 2005, David Roundy wrote:

 On Wed, Feb 23, 2005 at 12:27:19AM +, Terrence Brannon wrote:
  But anyway, here is the algorithm in case you don't enjoy tilting your
  head to read a page:
 
  Step 1. Write out message (HAIL ERIS) and put all vowels at the end
  (HLRSAIEI)
 
  Step 2. Reverse order (IEIASRLH)
 
  Step 3. Convert to numbers (9-5-9-1-19-18-12-8)
 
  Step 4. Put into numerical order (1-5-8-9-9-12-18-19)
 
  Step 5. Convert back to letter (AEHIILRS)
 
  This cryptographic cypher code is GUARANTEED TO BE 100% UNBREAKABLE
 
  .. so says the Principia Discordia. But I think we can generate and
  test to break it.

 Isn't it guaranteed unbreakable simply because there's no way to decrypt
 it? Since there isn't a one-to-one mapping of cyphertext to plaintext, I
 don't think it's actually a form of encryption.  Basically it's the same as
 the sort function, which is also not invertible.

yes, EXCEPT and EXPECT will get the same encryption ...

... and why is the order reversed (step 2) before the sorting (step 4) ?

___
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


Re: [Haskell-cafe] Re: new Haskell hacker seeking peer review

2005-02-23 Thread Andreas Farre

Bjorn Bringert said:

 Or why not the two characters shorter, but much less readable:

 pointsFreeCat' = getArgs = mapM_ ((= putStr) . readFile)

 or maybe:

 pointsFreeCat'' = getArgs = mapM_ (putStr . readFile)

 (.) :: (b - IO c) - (a - IO b) - a - IO c
 (.) = (.) . flip (=)

 Is (.) in the standard libs? If not, should it be? I'm sure there is a
 shorter definition of (.) that I haven't thought of.

 /Bjorn

Or even:

k :: Monad m = (a - m b) - Kleisli m a b
k = Kleisli

runKleisli :: Monad m = Kleisli m a b - (a - m b)
runKleisli (Kleisli f) = f

cat :: IO ()
cat = getArgs = (runKleisli $ (k $ mapM readFile)  (k $ mapM_ putStr))

after noticing that (.) is pretty similar to () when we lift (a - IO
b) to (Kleisli IO a b). It is pretty disappointing that runKleisli isn't
defined so that I can be cool and completely point free too ;)

/Andreas

-- 
some cannot be created more equal than others

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


Re: [Haskell-cafe] module Crypt_Discordian - code critique requested

2005-02-23 Thread Jacques Carette
Were I to write the same code as
Terrence Brannon [EMAIL PROTECTED] wrote:
module Crypt_Discordian 
where

import List
vowel_list = aeiouAEIOU
is_vowel c = c `elem` vowel_list
move_vowels lis = move_vowels' lis [] []
move_vowels' [] c v = v ++ c
move_vowels' (x:xs) c v
| is_vowel x  = move_vowels' xsc  (x:v)
| otherwise   = move_vowels' xs (x:c)v
remove_spaces str = filter (\x - x /= ' ') str
encrypt str = List.sort $ move_vowels $ remove_spaces str
I would likely write
module Foo where
vowel_list = aeiouAEIOU
split_vowels = partition (`elem` vowel_list)
tuple_to_list t = fst t ++ snd t
remove_spaces = filter (/= ' ') 

encrypt = List.sort . tuple_to_list . split_vowels . remove_spaces
instead.  But I have this feeling that tuple_to_list is probably already in 
the library, I just missed it.
The arbiters of good-Haskell-style can now enumerate the ways in which my code 
is 'bad' ;-)
Jacques
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] module Crypt_Discordian - code critique requested

2005-02-23 Thread Henning Thielemann

On Wed, 23 Feb 2005, Jacques Carette wrote:

 I would likely write
  module Foo where
 
  vowel_list = aeiouAEIOU
 
  split_vowels = partition (`elem` vowel_list)
 
  tuple_to_list t = fst t ++ snd t
 
  remove_spaces = filter (/= ' ')
 
  encrypt = List.sort . tuple_to_list . split_vowels . remove_spaces

 instead.  But I have this feeling that tuple_to_list is probably already in 
 the library, I just missed it.

do you mean
  uncurry (++)
 ?

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