Re: [Haskell-cafe] split string into n parts

2006-10-24 Thread Bulat Ziganshin
Hello jim,

Monday, October 23, 2006, 11:29:07 PM, you wrote:

 I want to split a string into 5 parts of equal length, with the last fifth
 padded if necessary, but can't get it right - here's what I've got - 

 fifths :: String - String
 fifths s = unwords [a1,a2,a3,a4,a5]
 where l = (length s) `div` 5
 s0 = s++
 (a1,s1) = splitAt l s0
 (a2,s2) = splitAt l s1
 ...

you can also use the following func:

splitByLen (len:lens) list  =  (x:splitByLens lens xs)where (x,xs) = 
splitAt len list
splitByLen [] []=  []

 

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Exception: Too many open files

2006-10-24 Thread Bulat Ziganshin
Hello Bas,

Tuesday, October 24, 2006, 1:03:55 AM, you wrote:

 Great it works! I didn't know about unsafeInterleaveIO [1].
 Why is it called 'unsafe'?
 And how does the laziness work? Is it because of the 'let r = ... in (s, r)'?

read either http://haskell.org/haskellwiki/IO_inside
or Simon's paper awkward squad mentioned there

in your original program, parseFile don't parsed file. it just
returned thunk (computation) that will parse file when data from this
thunk will be requested. so, your mapM returned 18k of such thunks,
each with its own file open. Tomasz's solution postpone not only
parsing, but the whole parseFile call (including file open) until the
data from this parsing will be really requested. because your next code
uses results of each parsing before using results of next one, this
allows garbage collector to close files of already used parsings
before you go to consume next one. smart solution

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Guards with do notation?

2006-10-24 Thread Joachim Breitner
Hi,

Am Dienstag, den 24.10.2006, 00:44 +0300 schrieb Misha Aizatulin:
 hello all,
 
why is it not possible to use guards in do-expressions like
 
do
  (a, b) | a == b - getPair
  return a and b are equal

Probably because it is not well-defined for all Monad what a failure is,
i.e. what to do in the other case. or something. Just my guess.

Greetings,
Joachim
-- 
Joachim nomeata Breitner
  mail: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Guards with do notation?

2006-10-24 Thread David House

On 24/10/06, Joachim Breitner [EMAIL PROTECTED] wrote:

Am Dienstag, den 24.10.2006, 00:44 +0300 schrieb Misha Aizatulin:
 hello all,

why is it not possible to use guards in do-expressions like

do
  (a, b) | a == b - getPair
  return a and b are equal

Probably because it is not well-defined for all Monad what a failure is,
i.e. what to do in the other case. or something. Just my guess.


Exactly the same thing that guards do elsewhere? Count the falsity of
the guard as a pattern match failure. It's precisely the same as
doing, e.g.:

do Just (a, b) - Nothing
  return a and b were Just

Pattern-match failure in a do-block invokes fail in that monad.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Guards with do notation?

2006-10-24 Thread Benjamin Franksen
Joachim Breitner wrote:

 Hi,
 
 Am Dienstag, den 24.10.2006, 00:44 +0300 schrieb Misha Aizatulin:
 hello all,
 
why is it not possible to use guards in do-expressions like
 
do
  (a, b) | a == b - getPair
  return a and b are equal
 
 Probably because it is not well-defined for all Monad what a failure is,
 i.e. what to do in the other case. or something. Just my guess.

No, fail is indeed a method of class Monad, and it is there exactly for this
reason, i.e. because pattern matching may fail (even without guards, think
of

  do
Just a - ...

) The restriction is there because guards are not allowed in lambda
expressions, for which do-notation is merely syntactic sugar. (Some people
have argued for lifting this restriction in Haskell', see
http://thread.gmane.org/gmane.comp.lang.haskell.prime/1750/focus=1750)

HTH
Ben

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


Re: [Haskell-cafe] Exception: Too many open files

2006-10-24 Thread Henning Thielemann

I don't know why these unsafe* functions are suggested so easily. Their
name is chosen for good reason.


On Mon, 23 Oct 2006, Bas van Dijk wrote:

 --
 module Main where
 
 import Text.ParserCombinators.Parsec
 
 data T = ...
 
 test = print . take 3 = parseFiles
 
 parseFiles :: IO [T]
 parseFiles = mapM parseFile = getFileFPs

Is it possible to turn it into

parseFiles :: [IO T]

?

Then you can easily do

sequence (take 3 parseFiles)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: split string into n parts

2006-10-24 Thread Jón Fairbairn
I wrote:
 jim burton [EMAIL PROTECTED] wrote:
  Thankyou! It's http://www.rubyquiz.com - They are mostly well suited to
  haskell, lot of mazes etc. I've done 5 or 6 with varying degrees of success
  but have learned a lot. This thing about strings in fifths is from #1, the
  solitaire cipher.
 
 At a quick glance I can't see which bit needs it. The only
 mention of five is where it asks to split the string into
 groups of five characters (not into five equal parts),
 padded with Xs.
 
 You can do that like this:
 
splitAtMb n l = let p = splitAt n l
in if null $ fst p
   then Nothing
   else Just p

Gah! Brain AWOL. I'm surprised no-one picked me up on
that. Why didn't I use:

splitAtMb n [] = Nothing
splitAtMb n l = Just $ splitAt n l

?

in_fives l = unfoldr (splitAtMb 5)
 (l ++ replicate (length l `mod` 5) 'X')

And using length makes this over-strict.

maybe something like

groups_of n = unfoldr (splitPad 5)
where splitPad [] = Nothing
  splitPad l = Just $ mapFst (padwith 'X') (splitAt n l)

padwith c l = take n $ l ++ replicate n c
mapFst f (a,b) = (f a, b) -- in Data.Graph.Inductive.Query.Monad

which is a little bit inefficient, but less clunky than
checking for the end of list in order to apply padwith just
once.

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: Guards with do notation?

2006-10-24 Thread Joachim Breitner
Hi,

Am Dienstag, den 24.10.2006, 12:48 +0200 schrieb Benjamin Franksen:
  Am Dienstag, den 24.10.2006, 00:44 +0300 schrieb Misha Aizatulin:
  hello all,
  
 why is it not possible to use guards in do-expressions like
  
 do
   (a, b) | a == b - getPair
   return a and b are equal
  
  Probably because it is not well-defined for all Monad what a failure is,
  i.e. what to do in the other case. or something. Just my guess.
 
 No, fail is indeed a method of class Monad, and it is there exactly for this
 reason, i.e. because pattern matching may fail (even without guards, think
 of
 
   do
 Just a - ...
 
 ) The restriction is there because guards are not allowed in lambda
 expressions, for which do-notation is merely syntactic sugar. (Some people
 have argued for lifting this restriction in Haskell', see
 http://thread.gmane.org/gmane.comp.lang.haskell.prime/1750/focus=1750)

Then why is the “guard” function, which can be used in a way to
implement what Misha wants, only available in MonadPlus, and not in
Monad?

Greetings,
Joachim
-- 
Joachim Breitner
  e-Mail: [EMAIL PROTECTED]
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Exception: Too many open files

2006-10-24 Thread Benjamin Franksen
Bas van Dijk wrote:
 On Monday 23 October 2006 21:50, Tomasz Zielonka wrote:
 unsafeInterleaveMapIO f (x:xs) = unsafeInterleaveIO $ do
 y - f x
 ys - unsafeInterleaveMapIO f xs
 return (y : ys)
 unsafeInterleaveMapIO _ [] = return []
 
 Great it works! I didn't know about unsafeInterleaveIO [1].
 
 Why is it called 'unsafe'?

Because it causes pure code to perform side-effects (=IO), albeit in a
controlled manner, so it's not as bad as unsafePerformIO. For instance,
using getContents you get a string (list of chars) with the property that
evaluating subsequent elements of the list causes IO to happen (in this
case reading another character from stdin). Thus, unsafeInterleaveIO is
safe only if it is not observable (from inside the program) when exactly
the IO gets performed.

Ben

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


[Haskell-cafe] Solitaire cipher

2006-10-24 Thread jim burton

I'm a beginner having a go at implementing the Solitaire cipher
(http://www.rubyquiz.com/quiz1.html as mentioned in another post) and I'd be
really grateful if you could help me improve the code to be neater  use
more functions from the Prelude etc, or errors (eg at the moment I can't
work out why padding accumulates after encrypting, decrypting?)...Thanks. 

*Main decrypt $ encrypt haskell is better by miles
HASKE LLISB ETTER BYMIL ESAYP X 
*Main decrypt $ encrypt $ decrypt $ encrypt haskell is better by miles
HASKE LLISB ETTER BYMIL ESAYP X BFCRK X 
*Main 
---

import Char
import Random
import List
import Foreign
import Maybe

data Card = Clubs Int | Spades Int | Diamonds Int | Hearts Int | JokerA |
JokerB 
deriving (Show, Eq)
type Deck = [Card]
--cardval - clubs are face value, diamonds plus 13, and so on - Jokers are
both 53
cardval  :: Card - Int
cardval (Clubs i)= i
cardval (Diamonds i) = i+13
cardval (Hearts i)   = i+26
cardval (Spades i)   = i+39
cardval _= 53

isJoker:: Card - Bool
isJoker JokerA = True
isJoker JokerB = True
isJoker _  = False
--take a card to a letter 
card2char :: Card - Char
card2char c = case c of
  (Clubs i)- int2alpha $ cardval c --can case fall
through in haskell?
  (Diamonds i) - int2alpha $ cardval c
  (Hearts i)   - int2alpha $ (cardval c-26)
  (Spades i)   - int2alpha $ (cardval c-26)
  _- error (Can't make  ++ show c ++
into alpha)
--take a letter to int, A=1, Z=26
char2int :: Char - Int
char2int = (64 `subtract`) . (ord)
--take a letter to int, 1=A, Z=26
int2alpha :: Int - Char
int2alpha = (chr) . (+64)

splitAtMb n l = let p = splitAt n l
   in if null $ fst p
  then Nothing
  else Just p

in_fives l = foldr (\x y - x++ ++y) [] $ unfoldr (splitAtMb 5)
 (l ++ replicate (5 - length l `mod` 5) 'X') 

--get an ordered deck
newdeck :: Deck
newdeck = suit 'c' ++ suit 'd' ++ suit 'h' ++ suit 's' ++ JokerA : JokerB :
[]
where suit s = case s of
  'c' - [Clubs i | i - [1..13]]
  's' - [Spades i | i - [1..13]]
  'd' - [Diamonds i | i - [1..13]]
  'h' - [Hearts i | i - [1..13]]

--key the deck ready to provide a keystream - move JokerA down one place,
--JokerB down 2 places, perform a triplecut then a countcut
keydeck :: Deck - Deck
keydeck = countcut. triplecut . (movedown JokerB) . (movedown JokerB) .
(movedown JokerA)

--bump a card down by one place in a deck, treating the deck as circular so
if the card is
-- last in the deck it becomes 2nd to front not 1st
movedown :: Eq a = a - [a] - [a]
movedown c d = if c == last d
   then head d : c : init (tail d)
   else top ++ bot!!1 : c : (tail (tail bot))
   where splt = splitAt (locate c d) d
 top = fst splt
 bot = snd splt
--substitute the cards above the first joker for those below the 2nd one
triplecut :: Deck - Deck 
triplecut d = afterLastJoker d ++ center d ++ beforeFirstJoker d
  where beforeFirstJoker = takeWhile (not . isJoker)
afterLastJoker = reverse . beforeFirstJoker . reverse 
center = reverse . dropWhile (not . isJoker) . reverse .
dropWhile (not . isJoker)

--get the value of the last card and move that many cards from the top of
deck to above the last card
countcut :: Deck - Deck
countcut d = init (drop n d) ++ take n d ++ [last d]
 where n = cardval (last d)

--key the deck, read the value of the top card as n, add the nth card to
stream, repeat
keystream :: Deck - String
keystream d = if isJoker c then keystream d' else card2char c : keystream d'
  where d' = keydeck d
c  = d'!!(cardval $ d'!!0)

locate :: Eq a = a - [a] - Int
locate x xs = fromJust (elemIndex x xs)

clean :: String - String
clean = map toUpper . filter isAlpha

encrypt, decrypt :: String - String
--encrypt a string using an unshuffled deck to start
encrypt = process (\x y - max26 (x+y))
where max26 x = if x  26 then x-26 else x
--decrypt a string using an unshuffled deck to start
decrypt = process (\x y - if x = y then (x+26)-y else x-y)

process :: (Int - Int - Int) - String - String
process f s = in_fives $ map int2alpha $ zipWith f ints1 ints2
where str1  = clean s
  str2  = take (length str1) (keystream newdeck)
  ints1 = map char2int str1
  ints2 = map char2int str2

-- 
View this message in context: 
http://www.nabble.com/Solitaire-cipher-tf2500700.html#a6971077
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Haskell beginner questions

2006-10-24 Thread jim burton



Cybertronic wrote:
 
 Hi all, I'm pretty much new to Haskell however I'm stuck on something
 which is that I'm trying to create a function called display where I type
 in a DVD name, e.g. dvd1, it returns d (String) and the multiplication of
 q (Int) and i (Double)
 
 Here's what I've done so far:
 
 type Film = (Int,String,Int,Double)
 
 dvd1 :: Film
 dvd1 = (1, Space, 5, 9.99)
 
 display :: Product - String
 display (c,d,q,i) = d
 
 My display function only shows the string but unfortunately I'm stuck on
 how to get the display function to multiply q (Int) and i (Double)
 together and display it next to d.
 
 Can someone help me out please? :)
 

I'd recommend a tutorial like
http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf 

 display :: Film - String
 display (c,d,q,i) = d ++   ++ show (fromIntegral q * i)

q needs to be converted first and show will convert the result to a string. 

-- 
View this message in context: 
http://www.nabble.com/Haskell-beginner-questions-tf2500050.html#a6971248
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Solitaire cipher

2006-10-24 Thread Chris Kuklewicz
There are several problems with the behavior:

 *Main encrypt 
 X 
 *Main decrypt $ encrypt 
 TANZP X 

So fixing this case would be the first thing to do, followed by:

 *Main encrypt hello
 LBVJW X 
 *Main decrypt $ encrypt hello
 HELLO YFRTQ X 


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


Re: [Haskell-cafe] Re: split string into n parts

2006-10-24 Thread Stefan Holdermans

Gah! Brain AWOL. I'm surprised no-one picked me up on
that. Why didn't I use:

splitAtMb n [] = Nothing
splitAtMb n l = Just $ splitAt n l


Actually, I've some code lying around doing exactly this (but without  
the padding ;)), written with the coalgebra inlined:


  split n = unfoldr $ \xs - case xs of
[] - Nothing
_  - Just (splitAt n xs)

Cheers,

  Stefan

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


Re: [Haskell-cafe] Solitaire cipher

2006-10-24 Thread jim burton



Chris Kuklewicz wrote:
 
 There are several problems with the behavior:
 
 *Main encrypt 
 X 
 *Main decrypt $ encrypt 
 TANZP X 
 
 So fixing this case would be the first thing to do, followed by:
 
 *Main encrypt hello
 LBVJW X 
 *Main decrypt $ encrypt hello
 HELLO YFRTQ X 
 
 

Thanks a lot, I think these are all related...some changes

in_fives l = trim $ foldr (\x y - x++ ++y) [] $ unfoldr (splitAtMb 5)
 (l ++ replicate n 'X') 
 where n = if m5 == 0 then 0 else 5 - m5
   m5 = length l `mod` 5

trim :: String - String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace

process :: (Int - Int - Int) - String - String
process f s = if null str1 then  else in_fives $ map int2alpha $ zipWith f
ints1 ints2
where str1  = trim $ clean s
  str2  = take (length str1) (keystream newdeck)
  ints1 = map char2int str1
  ints2 = map char2int str2

*Main decrypt $ encrypt $ decrypt $ encrypt hello
HELLO
*Main decrypt $ encrypt $ decrypt $ encrypt haskell is miles better
HASKE LLISM ILESB ETTER
*Main 

-- 
View this message in context: 
http://www.nabble.com/Solitaire-cipher-tf2500700.html#a6971503
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Re: Read a single Char

2006-10-24 Thread Hans van Thiel
Hello,

I have a similar question. When I use getChar with Hugs the newline
(caused by pressing 'Enter')  seems to be carried over into the next
call of main, where it is treated as a single input character. 
The workaround is getLine and head, but it would be nice to drop the
newline right away. I suppose the solution offered here: 

hSetBuffering stdin NoBuffering 

will have the desired effect, but is there another way?

Thanks,

Hans van Thiel

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


Re: [Haskell-cafe] Re: Read a single Char

2006-10-24 Thread Neil Mitchell

Hi


I have a similar question. When I use getChar with Hugs the newline
(caused by pressing 'Enter')  seems to be carried over into the next
call of main, where it is treated as a single input character.
The workaround is getLine and head, but it would be nice to drop the
newline right away. I suppose the solution offered here:


Hmm, sounds like a bug in WinHugs, I'll check it out.

Thanks

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


Re: [Haskell-cafe] Exception: Too many open files

2006-10-24 Thread Bas van Dijk
On Tuesday 24 October 2006 13:03, Henning Thielemann wrote:
 Is it possible to turn it into

 parseFiles :: [IO T]

 ?

 Then you can easily do

 sequence (take 3 parseFiles)

Thanks, I think I go for this sollution:

parseFiles :: IO [IO a]
parseFiles = liftM (map parseFile) getFileFPs

test = print = sequence . take 3 = parseFiles

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


[Haskell-cafe] Re: Solitaire cipher

2006-10-24 Thread Jón Fairbairn
jim burton [EMAIL PROTECTED] writes:

In addition to Chris's comments, here are some more:

 data Card = Clubs Int | Spades Int | Diamonds Int | Hearts Int | JokerA |
 JokerB 

They aren't really Ints; better to define something like

 data FaceValue = Ace | F2 | F3 | F4 | F5 | F6 | F7 | F8 | F9 | F10
| Jack | Queen | King

and possibly derive Enum (which unfortunately would give the
the wrong values, but that can be got around).

 deriving (Show, Eq)
 type Deck = [Card]
 --cardval - clubs are face value, diamonds plus 13, and so on - Jokers are
 both 53

I'd be inclined to define an Enum instance rather than
cardval directly, but define cardval as an auxilliary
function that scrunches both jokers to the same value.

 isJoker:: Card - Bool
 isJoker JokerA = True
 isJoker JokerB = True
 isJoker _  = False

Since you've defined an instance of Eq, you can use 

 isJoker c = c == JokerA || c == JokerB

 --take a card to a letter 
 card2char :: Card - Char
 card2char c = case c of
   (Clubs i)- int2alpha $ cardval c --can case fall
 through in haskell?

It's defined to, but you don't need a case clause as you can
use cardval and mod.

 --take a letter to int, A=1, Z=26
 char2int :: Char - Int
 char2int = (64 `subtract`) . (ord)

Better to use (ord 'A' - 1) if you are going to do it this
way.

 --take a letter to int, 1=A, Z=26
 int2alpha :: Int - Char
 int2alpha = (chr) . (+64)

and again

 splitAtMb n l = let p = splitAt n l
in if null $ fst p
   then Nothing
   else Just p

That was my mistake! Use the shorter, cleaner version I
posted after that one.

 in_fives l = foldr (\x y - x++ ++y) [] $ unfoldr (splitAtMb 5)
  (l ++ replicate (5 - length l `mod` 5) 'X') 

Putting the spaces in at this point is a mistake! Also see
what I said about length.

 --get an ordered deck
 newdeck :: Deck
 newdeck = suit 'c' ++ suit 'd' ++ suit 'h' ++ suit 's' ++ JokerA : JokerB :
 []
 where suit s = case s of
   'c' - [Clubs i | i - [1..13]]
   's' - [Spades i | i - [1..13]]
   'd' - [Diamonds i | i - [1..13]]
   'h' - [Hearts i | i - [1..13]]

That seems overly complicated. With an Enum instance, you'd just do

 newdeck = [Club Ace .. JokerB]

or better, with an instance of Bounded too,

 newdeck = [minBound .. maxBound]

Of course, you'd have to write toEnum to do the work, but
I'd do it something like

 toEnum 54 = JokerB
 toEnum 53 = JokerA
 toEnum n = [Club, Diamond, Heart, Spade]!!suit $ (toEnum (val+1))
where (suit, val) = (n-1) `divMod` 13

Comments from now on are a bit less thought through... I
think there are better ways to do some of these operations,
but I'm not going to present them, just nitpick a bit
instead.

 --key the deck ready to provide a keystream - move JokerA down one place,
 --JokerB down 2 places, perform a triplecut then a countcut
 keydeck :: Deck - Deck
 keydeck = countcut. triplecut . (movedown JokerB) . (movedown JokerB) .
 (movedown JokerA)
 
 --bump a card down by one place in a deck, treating the deck as circular so
 if the card is
 -- last in the deck it becomes 2nd to front not 1st
 movedown :: Eq a = a - [a] - [a]
 movedown c d = if c == last d

that looks like an unnecessary pass over the list

then head d : c : init (tail d)
else top ++ bot!!1 : c : (tail (tail bot))
where splt = splitAt (locate c d) d
  top = fst splt
  bot = snd splt

you can write 

 where (top,bot) = splitAt ...  But how about List.break?

And if you know that bot is going to have enough elements

 where (top, card1:card2:rest) = break ... 

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


[Haskell-cafe] Re: Re: Guards with do notation?

2006-10-24 Thread Benjamin Franksen
Joachim Breitner wrote:
 Am Dienstag, den 24.10.2006, 12:48 +0200 schrieb Benjamin Franksen:
  Am Dienstag, den 24.10.2006, 00:44 +0300 schrieb Misha Aizatulin:
  hello all,
  
 why is it not possible to use guards in do-expressions like
  
 do
   (a, b) | a == b - getPair
   return a and b are equal
  
  Probably because it is not well-defined for all Monad what a failure
  is, i.e. what to do in the other case. or something. Just my guess.
 
 No, fail is indeed a method of class Monad, and it is there exactly for
 this reason, i.e. because pattern matching may fail (even without guards,
 think of
 
   do
 Just a - ...
 
 ) The restriction is there because guards are not allowed in lambda
 expressions, for which do-notation is merely syntactic sugar. (Some
 people have argued for lifting this restriction in Haskell', see
 http://thread.gmane.org/gmane.comp.lang.haskell.prime/1750/focus=1750)
 
 Then why is the ?guard? function, which can be used in a way to
 implement what Misha wants, only available in MonadPlus, and not in
 Monad?

This seems to be inconsistent. Anyway, the decision to include fail in class
Monad (instead of using MonadZero) has been criticized by far more
competent people than me, see this thread

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/15656/focus=15666

Ben

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


Re: [Haskell-cafe] Solitaire cipher

2006-10-24 Thread jim burton


Jón Fairbairn-2 wrote:
 
 jim burton [EMAIL PROTECTED] writes:
 
 In addition to Chris's comments, here are some more:
 [snip]
 

Thanks for your comments Jon. I thought about making Cards an instance of
Enum but didn't realise how helpful it would be in various places.

I will use the shorter version of your function - I need to get a chance to
think about how it works first to be honest.

Haven't noticed divMod before - handy!

-- 
View this message in context: 
http://www.nabble.com/Solitaire-cipher-tf2500700.html#a6979284
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Re: Read a single Char

2006-10-24 Thread Hans van Thiel
No, it happens with Hugs on Fedora Core 5 (the fc5 Hugs package), not
WinHugs.

Thanks,

Hans

On Tue, 2006-10-24 at 17:27 +0100, Neil Mitchell wrote:
 Hi
 
  I have a similar question. When I use getChar with Hugs the newline
  (caused by pressing 'Enter')  seems to be carried over into the next
  call of main, where it is treated as a single input character.
  The workaround is getLine and head, but it would be nice to drop the
  newline right away. I suppose the solution offered here:
 
 Hmm, sounds like a bug in WinHugs, I'll check it out
 Thanks
 
 Neil

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


[Haskell-cafe] Re: Read a single char

2006-10-24 Thread Maurí­cio




Hi

 getChar doesn't return until I press Enter. I need something that
  returns immediately after I press any key.

It's a problem with buffering:

hSetBuffering stdin NoBuffering


This usually doesn't work on Windows:

GHC 6.4.2 and 6.6: requires enter
Hugs (console) Sept. 2006: requires enter
WinHugs (GUI) Sept. 2006: works as expected

But it seems to work on Linux:
GHC 6.4.1 on Ubuntu 6.06: works as expected
GHC 6.6 on Ubuntu 6.06: works as expected

I am really interested in hearing of a solution that works on all 
platforms.




  Does 'readKey', from System.Console.Readline, works on Windows? It 
works on Linux with the buffering advice applied.


  Maurício

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


Re: [Haskell-cafe] Re: Read a single Char

2006-10-24 Thread Neil Mitchell

No, it happens with Hugs on Fedora Core 5 (the fc5 Hugs package), not
WinHugs.


Woops, the previous post in a different thread was talking about
WinHugs, and I forgot to context-switch :)

Does GHCi give the different behaviour? If so, one of them is probably a bug.

Thanks

Neil



Thanks,

Hans

On Tue, 2006-10-24 at 17:27 +0100, Neil Mitchell wrote:
 Hi

  I have a similar question. When I use getChar with Hugs the newline
  (caused by pressing 'Enter')  seems to be carried over into the next
  call of main, where it is treated as a single input character.
  The workaround is getLine and head, but it would be nice to drop the
  newline right away. I suppose the solution offered here:

 Hmm, sounds like a bug in WinHugs, I'll check it out
 Thanks

 Neil



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


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread Dimitri Timofeev
Hi!Sorry if it is a bit off-topic in this thread.How can I input EOF symbol in WinHugs? Ctrl-Z and Ctrl-D don't work for me,so I can't use getContents function. Maybe there is a piece of documentationthat I should read?
Thanks!-- Dimitri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread Neil Mitchell

H


How can I input EOF symbol in WinHugs?


No possible way. If you could type the NUL character that might
possibly work, but even then 1) you can't, 2) it might not.

Do you have a particular need for typing the end of getContents in
WinHugs? If so, I can open a bug and might be able to fix it for the
next release.

Thanks

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


Re: [Haskell-cafe] Re: Read a single Char

2006-10-24 Thread John Meacham
On Tue, Oct 24, 2006 at 06:14:14PM +0200, Hans van Thiel wrote:
 I have a similar question. When I use getChar with Hugs the newline
 (caused by pressing 'Enter')  seems to be carried over into the next
 call of main, where it is treated as a single input character. 
 The workaround is getLine and head, but it would be nice to drop the
 newline right away. I suppose the solution offered here: 

that is the correct behavior, input is never discarded, it is just saved
up until you press enter for the first time. if you type fooenter,
your next four getChars will get 'f' 'o' 'o' and '\n'. it is not haskell
that is treating enter as specially, it is your terminal, getChar just
returns exactly what was passed to it.
 
 hSetBuffering stdin NoBuffering 
 
 will have the desired effect, but is there another way?

this will cause getChar to return right away as soon as they type the
first character. which is probably what you want. of course, if they
press an enter, you will see an enter. but you don't have to wait until
they press one.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread Dimitri Timofeev
On 10/25/06, Neil Mitchell [EMAIL PROTECTED] wrote:
 How can I input EOF symbol in WinHugs?No possible way. If you could type the NUL character that mightpossibly work, but even then 1) you can't, 2) it might not.Do you have a particular need for typing the end of getContents in
WinHugs? If so, I can open a bug and might be able to fix it for thenext release.Thank you!Surely I can get along without getContents in WinHugs: last time I thought aboutit I just wanted to show getContents function to my students (and using hGetContents
on a file handle seems to be better example). Another function thatcould be useful when teaching IO is 'interact', and it seems that it's alsoimpossible to use it without typing EOF (am I right?).So it would be nice to have a way to type EOF in WinHugs, but surely it's a
feature one can live without.And thank you for WinHugs, it is really useful!-- Dimitri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread John Meacham
On Wed, Oct 25, 2006 at 01:06:28AM +0400, Dimitri Timofeev wrote:
 Sorry if it is a bit off-topic in this thread.
 How can I input EOF symbol in WinHugs? Ctrl-Z and Ctrl-D don't work for me,
 so I can't use getContents function. Maybe there is a piece of documentation
 that I should read?

does F6 work? it used to back with DOS something or another.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread Dimitri Timofeev
On 10/25/06, John Meacham [EMAIL PROTECTED] wrote:
does F6 work? it used to back with DOS something or another.It works in console Hugs, as well as Ctrl-Z, but does not work in WinHugs.-- Dimitri
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Read a single char

2006-10-24 Thread Neil Mitchell

Hi


Surely I can get along without getContents in WinHugs: last time I thought
about
it I just wanted to show getContents function to my students (and using
hGetContents
on a file handle seems to be better example). Another function that
could be useful when teaching IO is 'interact', and it seems that it's also
impossible to use it without typing EOF (am I right?).


You can use interact, you just have to hit the stop button to break
out of it. Interestingly Ctrl+C is captured by interact, as is
Ctrl+Z/Ctrl+D, so fixing it up to return -1 in these cases should be
pretty easy - i'll try and get that done tomorrow.


And thank you for WinHugs, it is really useful!


Thank you :) - its nice to know that it is being used.

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


[Haskell-cafe] Re: Configurations proposal

2006-10-24 Thread Brian Smith
On 10/24/06, Duncan Coutts [EMAIL PROTECTED] wrote:
On the other hand, in Gtk2Hs I know one case where we do this. We have aGraphics.UI.Gtk.Cairo api module that is only included if Gtk was builtagainst Cairo. In any case it could be faked by using cpp to just not
export anything rather than not having the module exposed at all. Soit's not clear that it's worth banning. Or maybe making it slightlyharder is worth it so that people don't get in the habit.
Couldn't you split this into Gtk and Gtk-Cairo packages, where the latter is only built if Cairo is available? Similarly, in your GUI example, couldn't you have seperate foo and foo-gui packages, and only build the foo-gui package if the GUI libraries are available?
Otherwise, how can you say I depend on the Gtk package being built with Cairo support and I depend on the GUI portion of the foo package?In general, optional groups of modules should be split off into separate packages, and there should be a way of building a bundle of related packages together (just like one can build a group of related executables together already).
Regards,Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell custom search engine

2006-10-24 Thread Donald Bruce Stewart
Google now lets us create our own custom search engine pages, so I
whipped one up for Haskell,

http://www.google.com/coop/cse?cx=015832023690232952875%3Acunmubfghzq

also, as a demo, embedded

http://www.cse.unsw.edu.au/~dons/search.html

Seems to do a reasonable job of targetting just Haskell sites. Feel free
to add more Haskell material, or refine the search. In fact, search for
mailing list items seems rather easy this way.

Neil, I wonder if we could integrate this with Hoogle somehow?

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