Re[2]: [Haskell-cafe] deepSeq vs rnf

2006-10-23 Thread Bulat Ziganshin
Hello Cale,

Monday, October 23, 2006, 7:19:14 AM, you wrote:

 Speaking of boilerplate and the scrapping thereof, Data.Generics could
 theoretically also be used to write a relatively generic rnf/deepSeq,
 but in my attempts, it seems to be much much slower than using a
 specific normal form class. Here's my code from quite a while back. As
 I recall, it's semantically correct, but ran about an order of
 magnitude slower. There might be a much better way to do it, I don't
 really know Data.Generics all that well.

by no means it's surprising - syb library works slower than
hand-written or compile-time generated code because it implements
_run-time_ polymorphism - data types are tested at run-time and then
coerced to their actual types. there is also syb4 approach by Oleg
where type classes used for polymorphism - it should have average
speed, in theory


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re[2]: [Haskell] Pugs gains SMP parallelism support.

2006-10-23 Thread Bulat Ziganshin
Hello Taral,

Monday, October 23, 2006, 1:12:38 PM, you wrote:

 They probably are. However you get the overhead of creating the array
 (when you don't really need O(1) random access) and every thread
 signals the same semaphore which may lead to some congestion which
 could slow things down.

 You do need O(1) random access for the writers to put their results in
 efficiently. And newArray_ should be faster than N copies of
 newEmptyMVar. It is true that I have one congestion point (the
 semaphone) instead of N (the mvars).

are you sure that writeArray calls may be overlapped? :) they may
change some technical fields, such as 'dirty' bit



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: (more) type level functions (type of decreasing list)

2006-10-23 Thread Greg Buchholz
[EMAIL PROTECTED] wrote:
] 
] One way is to use existentials:
] 

 data Seq1 a = forall b. (Pre a b, Show b) = Cons1 a (Seq1 b) | Nil1

] 
] which perhaps not entirely satisfactory because we have to specify all
] the needed classes in the definition of Seq1.

Yes, that seems pretty burdensome, since we can't now create even a
simple function like tail, right?  Or at least I think existentials
are the problem with this...

 tail1 :: (Pre a b, Show b) = Seq1 a - Seq1 b
 -- tail1 (Cons1 x xs) = xs
 tail1 Nil1 = error empty Seq

...ghci reports...

Couldn't match expected type `b' (a rigid variable)
   against inferred type `b1' (a rigid variable)
  `b' is bound by the type signature for `tail_' at dec2.lhs:30:17
  `b1' is bound by the pattern for `Cons1' at dec2.lhs:31:8-17
  Expected type: Seq1 b
  Inferred type: Seq1 b1
In the expression: xs
In the definition of `tail1': tail1 (Cons1 x xs) = xs

...and hugs...

 ERROR dec2.lhs:31 - Existentially quantified variable in inferred type
 *** Variable : _3
 *** From pattern : Cons1 x xs
 *** Result type  : Seq1 _0 - Seq1 _3

] 
] Perhaps a better -- and a more general alternative -- is to use
] type-level programming to its fullest. The following defines a list
] whose elements are constrained to be in the decreasing, increasing,
] or any other (defined in the future) order. This example shows that
] Haskell truly has more kinds than it is commonly acknowledged.

snip

]  data Cons a b = Cons a b
]  data Nil = Nil

...if we build our lists with tuple-like Conses, our types end up being
as long as our lists, right?  So an infinite list has an infinite type,
which seems like it could be problematic to type check.  For example,
here's an arbitrarly long increasing list...

 data Seq' a = Cons' a (Seq' (Succ a)) | Nil' deriving Show

 from :: a - Seq' a
 from x = Cons' x (from (S x))

 inf = from Z

...with some of the usual functions...

 tail_ :: Seq' a - Seq' (Succ a)
 tail_ (Cons' x xs) = xs

 class Take a where 
 take_ :: a - (Seq' b) - (Seq' b)

 instance Take Zero where 
 take_ Z _ = Nil'
 
 instance Take a = Take (Succ a) where
 take_ (S n) (Cons' x xs) = Cons' x (take_ n xs)
 take_ _ Nil' = error can't take_ that many

 class Drop a b c | a b - c where
 drop_ :: a - Seq' b - Seq' c

 instance Drop Zero b b where
 drop_ Z xs = xs

 instance Drop a (Succ b) c = Drop (Succ a) b c where
 drop_ (S n) (Cons' x xs) = drop_ n xs
 drop_ _ Nil' = error can't drop_ that many

...Anyway, for fun, here's a list that alternates between two types in a
linearly increasing manner.  So you can start out with one Int and then
two Strings, then three Ints, four Strings, etc.  I don't know if it is
going to yeild to a type classless GADT solution yet, but I'll keep
thinking about it.


 data Fancy a b left next =  
 forall c d left' next' lz decleft .
 (Show c, Show d,
  Zerop left lz,
  If lz (Succ next) next next',
  Pre left decleft,
  If lz next decleft left',
  If lz b a c,
  If lz a b d
 ) = Cons a (Fancy c d left' next') | Nil
 
 fancy :: Fancy Integer String Zero (Succ Zero)
 fancy = (Cons 1 
 (Cons a (Cons b 
 (Cons  2  (Cons  3  (Cons 4 
 (Cons c (Cons d (Cons e (Cons f
 (Cons  5  (Cons  6  (Cons  7  (Cons  8  (Cons 9 Nil)))

 instance (Show a, Show b) = Show (Fancy a b c d) where
 show (Cons x xs) = (Cons  ++ (show x) ++   ++ (show xs) ++ )
 show Nil = Nil

 data Succ a = S a deriving Show
 data Zero = Z deriving Show 
 
 data TTrue
 data TFalse
 
 class Pre a b | a - b 
 instance Pre (Succ a) a
 instance Pre Zero Zero
 
 class If p t e result | p t e - result
 instance If TTrue  a b a
 instance If TFalse a b b
 
 class Zerop a b | a - b
 instance Zerop Zero TTrue
 instance Zerop (Succ a) TFalse
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Exception: Too many open files

2006-10-23 Thread Bas van Dijk
Hello Haskellers,

I'm wondering how to get the following to work:

I need to parse about 18.000 files. I would like to have a 
function 'parseFiles' that parses all these files and returns the result in a 
list.

When I execute 'test' from the simplified code below I get the error:

*** Exception: file_0014994.txt: openFile: resource exhausted (Too many open 
files)

So it seems that 'parseFiles' tries to open all the ~18.000 files and gets 
exhausted when opening the 14994 file.

What I would like is 'take 3 = parseFiles' to read only the first 3 files.

Is this possible, and if so, what is the best way to do this?

Note that the code below is a bit simplified:

--
module Main where

import Text.ParserCombinators.Parsec

data T = ...

test = print . take 3 = parseFiles

parseFiles :: IO [T]
parseFiles = mapM parseFile = getFileFPs

getFileFPs :: IO [FilePath]
getFileFPs = ... -- returns a large list of about 18.000 FilePaths

parseFile ::  FilePath - IO T
parseFile fp = liftM getRight $ parseFromFile someParser fp

getRight (Right r) = r

someParser :: Parser T
someParser = ...
--

Greetings,

Bas van Dijk

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


[Haskell-cafe] split string into n parts

2006-10-23 Thread jim burton

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 = fifths'  0 s
 where l = (length s) `div` 5
   fifths' xs c [] = xs ++ (replicate (l-c) 'X')
   fifths' xs c (y:ys) = if c == l 
 then fifths' (xs++[' ',y]) 0
 ys 
 else fifths' (xs++[y]) (c+1)
 ys 

which, apart from surely being uglier than need be, doesn't work:

*Main fifths IDOLIKETOBEBESIDETHESEASIDE
IDOLI KETOBE BESIDE THESEA SIDEXX
*Main fifths 12345
1 23 45

Any thoughts? Thanks! This isn't homework BTW, I'm having a go at the ruby
quiz puzzles in haskell, which seems to be a nice way to learn.
-- 
View this message in context: 
http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6960346
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] Exception: Too many open files

2006-10-23 Thread Tomasz Zielonka
On Mon, Oct 23, 2006 at 08:48:24PM +0200, Bas van Dijk wrote:
 So it seems that 'parseFiles' tries to open all the ~18.000 files and gets 
 exhausted when opening the 14994 file.
 
 What I would like is 'take 3 = parseFiles' to read only the first 3 files.
 
 Is this possible, and if so, what is the best way to do this?

 parseFiles :: IO [T]
 parseFiles = mapM parseFile = getFileFPs

use this function instead of mapM above:

unsafeInterleaveMapIO f (x:xs) = unsafeInterleaveIO $ do
y - f x
ys - unsafeInterleaveMapIO f xs
return (y : ys)
unsafeInterleaveMapIO _ [] = return []

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


[Haskell-cafe] split string into n parts

2006-10-23 Thread Paul Brown

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 = fifths'  0 s
 where l = (length s) `div` 5
[... snip ...]
Any thoughts? Thanks! This isn't homework BTW, I'm having a go at the ruby
quiz puzzles in haskell, which seems to be a nice way to learn.


Cool idea!  Can you post a link for the puzzles?

As for this one, don't you want the first multiple of five larger than
the length of the string?  You should be able to make things simpler
if you auto-pad the string from the get-go (forgive any syntax errors,
as I'm just composing in a browser here...):

prepad :: Integer - String - String
prepad n s | (length s) `mod` n == 0 = s
prepad n s = prepad n (s ++ ' ')

And now you can be sneaky:

nths :: Integer - String - String
nths n s = [first_nth n s] ++ nths (n-1) (after_first_nth n s)
nths 1 s = s

Where first takes the first n chars (e.g., take ((length s) `div` n))
and after_first_nth returns the tail of the list..

--
[EMAIL PROTECTED]
http://mult.ifario.us/


--
[EMAIL PROTECTED]
http://mult.ifario.us/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-10-23 Thread Mark T.B. Carroll
jim burton [EMAIL PROTECTED] writes:

 I want to split a string into 5 parts of equal length, with the last fifth
 padded if necessary
(snip)
 *Main fifths 12345
 1 23 45

What's the correct answer for fifths 123456? I can't figure out how to
meet both your constraints. Is 12 34 56 XX XX permitted (padding
before fifth as well)?

-- Mark

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


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

2006-10-23 Thread jim burton



Paul Brown-4 wrote:
 
 Cool idea!  Can you post a link for the puzzles?
 
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.

 
 As for this one, don't you want the first multiple of five larger than
 the length of the string?  You should be able to make things simpler
 if you auto-pad the string from the get-go (forgive any syntax errors,
 as I'm just composing in a browser here...):
 
 [snip]
 
Good plan! I will play with that.
-- 
View this message in context: 
http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6961186
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] split string into n parts

2006-10-23 Thread Mark T.B. Carroll
jim burton [EMAIL PROTECTED] writes:
(snip)
 *Main fifths IDOLIKETOBEBESIDETHESEASIDE
 IDOLI KETOBE BESIDE THESEA SIDEXX
 *Main fifths 12345
 1 23 45
(snip)

FWIW this unholy thing works for me,

fifths :: String - String

fifths = splitIntoN 5

splitIntoN :: Int - String - String

splitIntoN n string = 
let stringToSplit = string ++ replicate (n-1) 'X'
in unwords (map fst (take n (tail (iterate (splitAt (div (length 
stringToSplit) n) . snd) (undefined, stringToSplit)

Admittedly, a 'let' might be nice to name some intermediate
computations.

-- Mark

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


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

2006-10-23 Thread jim burton



Mark T.B. Carroll-2 wrote:
 
 
 FWIW this unholy thing works for me,
 
 fifths :: String - String
 
 fifths = splitIntoN 5
 
 [snip]
 
 
Thanks Mark.
-- 
View this message in context: 
http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6961461
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] split string into n parts

2006-10-23 Thread Rich Neswold
On 10/23/06, jim burton [EMAIL PROTECTED] 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
I got this:fifths :: String - Stringfifths xs = let len = (length xs + 4) `div` 5 padded = take (len * 5) (xs ++  ) in unwords $ nth len padded
 where nth _ [] = [] nth n xs = (take n xs) : (nth n $ drop n xs) *Main fifths IDOLIKETOBEBESIDETHESEASIDE IDOLI KETOBE BESIDE THESEA SIDEXX *Main fifths 12345
 1 23 45This gives the following results:IDOLIK ETOBEB ESIDET HESEAS IDE and1 2 3 4 5But it also gives this result, which may or may not be correct for your problem:
*Main fifths 12345612 34 56 -- RichAIM : rnezzyICQ : 174908475
___
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-23 Thread Jón Fairbairn
jim burton [EMAIL PROTECTED] writes:

 Paul Brown-4 wrote:
  
  Cool idea!  Can you post a link for the puzzles?
  
 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

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

To break a string into five equal parts with the last padded
with Xs, try this:

   fifths l = let len = length l
  part_length = (len+4)`div`5
  pad_length = 5*part_length - len
  in unfoldr (splitAtMb part_length)
 (l ++ replicate pad_length 'X')

I haven't checked these at all carefully, but at least they
illustrate the use of unfoldr.  [aside: One might argue that
the prelude ought to provide splitAtMb rather than splitAt.]

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


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

2006-10-23 Thread jim burton



Jón Fairbairn-2 wrote:
 
 
 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.
 
Oh dear, you're right. Sorry, I read in a rush. Thanks for the solution too.


Jón Fairbairn-2 wrote:
 
 You can do that like this:
 
splitAtMb n l = let p = splitAt n l
in if null $ fst p
   then Nothing
   else Just p
 
in_fives l = unfoldr (splitAtMb 5)
 (l ++ replicate (length l `mod` 5) 'X')
 
 To break a string into five equal parts with the last padded
 with Xs, try this:
 
fifths l = let len = length l
   part_length = (len+4)`div`5
   pad_length = 5*part_length - len
   in unfoldr (splitAtMb part_length)
  (l ++ replicate pad_length 'X')
 
 I haven't checked these at all carefully, but at least they
 illustrate the use of unfoldr.  [aside: One might argue that
 the prelude ought to provide splitAtMb rather than splitAt.]
 
 -- 
 Jón Fairbairn [EMAIL PROTECTED]
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6961825
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] split string into n parts

2006-10-23 Thread jim burton

tweak to in_fives

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

-- 
View this message in context: 
http://www.nabble.com/split-string-into-n-parts-tf2496941.html#a6961912
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: split string into n parts

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

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

Whoops! Yes.  And a slapped wrist for me for writing a
constant three times. Serves me right for not writing

groups_of n l = unfolder (splitAtMb n) ...
in_fives = groups_of 5

:-)


-- 
Jón Fairbairn [EMAIL PROTECTED]


___
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-23 Thread Bas van Dijk
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'?

And how does the laziness work? Is it because of the 'let r = ... in (s, r)'? 

[1] ghc/libraries/base/GHC/IOBase.lhs:249:
---
{-|
'unsafeInterleaveIO' allows 'IO' computation to be deferred lazily.
When passed a value of type @IO a@, the 'IO' will only be performed
when the value of the @a@ is demanded.  This is used to implement lazy
file reading, see 'System.IO.hGetContents'.
-}
{-# INLINE unsafeInterleaveIO #-}
unsafeInterleaveIO :: IO a - IO a
unsafeInterleaveIO (IO m)
  = IO ( \ s - let
   r = case m s of (# _, res #) - res
in
(# s, r #))

-- We believe that INLINE on unsafeInterleaveIO is safe, because the
-- state from this IO thread is passed explicitly to the interleaved
-- IO, so it cannot be floated out and shared.
---

Thanks,

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


[Haskell-cafe] Guards with do notation?

2006-10-23 Thread 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

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


[Haskell-cafe] Segmentation fault with realdine library

2006-10-23 Thread Maurí­cio

  Hi,

  This small program says Segmentation fault:

module Main (Main.main) where
import Data.Char
import System.Time
import System.Console.Readline
main :: IO ()
main = do
readKey
return ()

  I don't understand anything about readline, so I probably should have 
to call some function before readKey (by they way, I don't know what 
readKey does). But I thought a segmentation fault is always something to 
be reported.


  Best,
  Maurício

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


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

2006-10-23 Thread Udo Stenzel
jim burton 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 s = unwords.take 5.unfoldr (Just . splitAt l) $ s ++ repeat ' '
  where l = (length s + 4) `div` 5 


Of course no Haskeller in his right mind would carelessly apply the
final 'unwords' unless this was for immediate output.


Udo.
-- 
The Second Law of Thermodynamics:
If you think things are in a mess now, just wait!
-- Jim Warner


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


Re: [Haskell-cafe] Segmentation fault with realdine library

2006-10-23 Thread Duncan Coutts
On Mon, 2006-10-23 at 20:18 -0200, Maurí­cio wrote:
Hi,
 
This small program says Segmentation fault:
 
 module Main (Main.main) where
 import Data.Char
 import System.Time
 import System.Console.Readline
 main :: IO ()
 main = do
  readKey
  return ()
 
I don't understand anything about readline, so I probably should have 
 to call some function before readKey (by they way, I don't know what 
 readKey does). But I thought a segmentation fault is always something to 
 be reported.

Yes, I get the same result. It seems that one must use 'initialise'
first. I agree, it would be much nicer if you didn't have to do this and
if instead it would Just Worktm.

Duncan

___
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-23 Thread Bas van Dijk
On Tuesday 24 October 2006 00:58, Greg Fitzgerald wrote:
  test = print . take 3 = parseFiles

 I haven't had time to double-check this code, but something like this ought
 to work (no 'unsafe' operations!):
 test = sequence . take 3 . map (print . parseFile) = getFileFPs

 Let me know how it goes.

Indeed, the following works:

test = sequence . take 3 . map (\fp - print = parseFile fp) = getFileFPs

Thanks,

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


[Haskell-cafe] Read a single char

2006-10-23 Thread Maurí­cio

  Hi,

  How can I read a single character from standard output? I would like 
the user to press a single key and the reading function return 
imediately after that key is pressed.


  Thanks,
  Maurício

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


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

2006-10-23 Thread Clifford Beshers





Udo Stenzel wrote:

  jim burton 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 s = unwords.take 5.unfoldr (Just . splitAt l) $ s ++ repeat ' '
  where l = (length s + 4) `div` 5 
  



Okay, you win. That's the nicest answer so far, I think.

But here are solutions with a different theme altogether. They are
based on groupBy, not unfoldr. I really like the new `on` function.


module Chunk where

import Data.List

(on) f g = \x y - f (g x) (g y)

groupByIndex test xs =
 map (map snd) $ groupBy (test `on` fst) $ zip [0..] xs

-- chunk : divide the input string into n chunks of equal length (len),
with padding

-- chunk1 accepts the number of chunks
chunk1 n pad xs = 
 unwords $ take n $ groupByIndex ((==) `on` (`div` len)) $ xs ++
repeat pad
 where len = (length xs + n - 1) `div` n

-- chunk2 accepts the length of each chunk
chunk2 len pad xs = 
 unwords $ take n $ groupByIndex ((==) `on` (`div` len)) $ xs ++
repeat pad
 where n = (length xs + len - 1) `div` len



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


Re: [Haskell-cafe] Read a single char

2006-10-23 Thread Donald Bruce Stewart
briqueabraque:
   Hi,
 
   How can I read a single character from standard output? I would like 
 the user to press a single key and the reading function return 
 imediately after that key is pressed.

so you want a function of type:
IO Char

asking Hoogle (http://haskell.org/hoogle) we get:
Prelude.  getChar:: IO Char
IO.   hGetChar   :: Handle - IO Char

-- Don

___
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-23 Thread Neil Mitchell

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:

http://haskell.org/hoogle/?q=buffering

suggests:

hSetBuffering stdin NoBuffering

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-23 Thread Brian Smith
On 10/23/06, Neil Mitchell [EMAIL PROTECTED] wrote:
HigetChar 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 enterHugs (console) Sept. 2006: requires enter
WinHugs (GUI) Sept. 2006: works as expectedBut it seems to work on Linux:GHC 6.4.1 on Ubuntu 6.06: works as expectedGHC 6.6 on Ubuntu 6.06: works as expectedI am really interested in hearing of a solution that works on all platforms.
 import IO main = do hSetBuffering stdin NoBuffering hGetChar stdinRegards,Brian 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe