Re: [Haskell-cafe] Memory usage of cabal install

2009-04-27 Thread Krzysztof Kościuszkiewicz
On Mon, Apr 27, 2009 at 02:10:28PM +0100, Duncan Coutts wrote:

> If you're using ghc 6.10 then the solution is to update to cabal-install
> 0.6.x. If you're quite sure you are using 6.8 then the bug is unknown.
> It may still be worth trying upgrading to cabal-install 0.6.x.

I've upgraded to cabal-install 0.6.2 and the problem went away.

Thanks for help!
-- 
Krzysztof Kościuszkiewicz
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memory usage of cabal install

2009-04-27 Thread Krzysztof Kościuszkiewicz
On Mon, Apr 27, 2009 at 02:10:28PM +0100, Duncan Coutts wrote:

> > [...]
> > Increasing verbosity does not help, memory consumption goes up after the
> > message "Resolving dependencies..." shows up.
> > 
> > I use ghc 6.8.2 and cabal-install version 0.5.1 using version 1.4.0.1 of
> > the Cabal library.
> 
> The only instance of this behaviour that I know of involves using that
> version of cabal-install with ghc-6.10.1.
> 
> http://haskell.org/cabal/FAQ.html#cabal-goes-into-an-infinite-loop--runs-out-of-memory
>
> [...]
>
> Are you absolutely sure you are using ghc 6.8 and not 6.10?

Yes:

> k...@copper:~$ ghc -V ; cabal -V
> The Glorious Glasgow Haskell Compilation System, version 6.8.2
> cabal-install version 0.5.1
> using version 1.4.0.1 of the Cabal library 

> > Is there a workaround? I would like to avoid fetching & building packages
> > manually.
> 
> If you're using ghc 6.10 then the solution is to update to cabal-install
> 0.6.x. If you're quite sure you are using 6.8 then the bug is unknown.
> It may still be worth trying upgrading to cabal-install 0.6.x.

I'll try that and report success/failure.

Thanks,
-- 
Krzysztof Kościuszkiewicz
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Memory usage of cabal install

2009-04-27 Thread Krzysztof Kościuszkiewicz
Hello Haskell-Café,

I have a problem with high memory usage of cabal-install.  Whenever I
try to install or upgrade a package, cabal manages to consume 1,3G of
memory before I killed it (on a 32-bit machine with 1 GB of memory).

Increasing verbosity does not help, memory consumption goes up after the
message "Resolving dependencies..." shows up.

I use ghc 6.8.2 and cabal-install version 0.5.1 using version 1.4.0.1 of
the Cabal library.

Is there a workaround? I would like to avoid fetching & building packages
manually.
-- 
Krzysztof Kościuszkiewicz
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell stacktrace

2008-09-09 Thread Krzysztof Kościuszkiewicz
On Tue, Sep 09, 2008 at 11:06:43PM +0200, Pieter Laeremans wrote:
> This :
> Prelude> let f = (\x -> return "something went wrong")  ::   IOError -> IO
> String
> Prelude> let t = return $ show $ "too short list" !! 100 :: IO String
> Prelude> catch t f
> "*** Exception: Prelude.(!!): index too large

How about:

> module Main where
>
> import Control.Exception
> import Prelude hiding (catch)
>
> f :: Exception -> IO String
> f = const $ return "sthg went wrong"
>
> g :: String
> g = show $ "too short list" !! 100
>
> h :: IO String
> h = do
>   print $ head [0 .. -1]
>   return "huh?"
>
> main = do
>   mapM_ print =<< sequence
>   [ h `catch` f
>   , evaluate g `catch` f
>   , (return $! g) `catch` f
>   , (return g) `catch` f
>   ]

Output:

[EMAIL PROTECTED]:/tmp$ runhaskell test.lhs
"sthg went wrong"
"sthg went wrong"
"sthg went wrong"
"test.lhs: Prelude.(!!): index too large

Check documentation of catch and evaluate functions in Control.Exception.

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Krzysztof Kościuszkiewicz
On Mon, Apr 07, 2008 at 07:51:05PM -0700, Jackm139 wrote:

> I have an assignment to make a program to test whether two lists use the
> same characters for each string.
> e.g.
> 
> sameCharacter ["rock", "cab"] ["cork", "abc"]
> True
> 
> My plan to tackle this was to use:
> nub to eliminate duplications,
> sort to put the characters in order,
> and map to put characters together.. and then somehow check to see if these
> characters are the same.

Probably you won't need to eliminate duplicates, sorting would be enough
(although it depends on the assignment details).

Comparing Chars (and Strings) can be accomplished with

> (==) :: (Eq a) => a -> a -> Bool

> My problem right now is just figuring out how to make a function that uses
> these three functions to give me a list of tuples.

To get list of tuples you can use

> zip :: [a] -> [b] -> [(a, b)]

or alternatively you can apply a binary function in a "pairwise way"
using

> zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]

as in

> zipWith (+) [1, 2] [3, 4]
> [4, 6]

For chaining functions you can use function composition:

> (.) :: (b -> c) -> (a -> b) -> a -> c

as in

> not :: Bool -> Bool
> and :: [Bool] -> Bool
> nand :: [Bool] -> Bool
> nand = not . and

or do without composition by specifying all arguments:

> nand xs = not (and xs)

Hope this helps,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leak - help needed

2008-03-13 Thread Krzysztof Kościuszkiewicz
On Wed, Mar 12, 2008 at 12:34:38PM -0700, Justin Bailey wrote:

> The stack blows up when a bunch of unevaluated thunks build up, and
> you try to evaluate them. One way to determine where those thunks are
> getting built is to use GHCs "retainer" profiling. Retainer sets will
> show you the "call stack" that is holding on to memory. That can give
> you a clue where these thunks are being created. To get finer-grained
> results, annotate your code with {#- SCC "..." #-} pragmas. Then you
> can filter the retainer profile by those annotations. That will help
> you determine where in a given function the thunks are being created.
> 
> If you need help with profiling basics, feel free to ask.

I'm not entirely sure if I understand retainer profiling correctly... So
please clarify if you spot any obvious blunders.

Retainers are thunks or objects on stack that keep references to
live objects. All retainers of an object are called the object's
retainer set.  Now when one makes a profiling run, say with ./jobname
+RTS -p -hr, the graph refernces retainer sets from jobname.prof. My
understanding is that it is the total size of all objects retained by
retainer sets being plotted, correct?

About decoding the sets from jobname.prof - for example in

> SET 2 = {}
> SET 16 = {, }
> SET 18 = {, }

{...} means it's a set, and  is the retainer cost centre
(ccN) and hierarchy of parent cost centres up to the "top level" (cc0)?

My understanding is that SET 18 above refers to objects that are
retained by exactly two specified cost centres, right?

Finally, what is the MAIN.SYSTEM retainer?

Thanks in advance,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leak - help needed

2008-03-13 Thread Krzysztof Kościuszkiewicz
On Thu, Mar 13, 2008 at 05:52:05PM +0100, Bertram Felgenhauer wrote:

> > ... Now evaluation of the parser state blows the stack...
> > 
> > The code is at http://hpaste.org/6310
> 
> Apparently, stUpdate is too lazy. I'd define
> 
> stUpdate' :: (s -> s) -> Parser s t ()
> stUpdate' f = stUpdate f >> stGet >>= (`seq` return ())
> 
> and try using stUpdate' instead of stUpdate in incCount.

Yes, that solves the stack issue. Thanks!
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leak - help needed

2008-03-12 Thread Krzysztof Kościuszkiewicz
On Mon, Mar 03, 2008 at 05:20:09AM +0100, Bertram Felgenhauer wrote:

> > Another story from an (almost) happy Haskell user that finds himself
> > overwhelmed by laziness/space leaks.
> > 
> > I'm trying to parse a large file (>600MB) with a single S-expression
> > like structure. With the help of ByteStrings I'm down to 4min processing
> > time in constant space. However, when I try to wrap the parse results
> > in a data structure, the heap blows up - even though I never actually
> > inspect the structure being built! This bugs me, so I come here looking
> > for answers.
> 
> The polyparse library (http://www.cs.york.ac.uk/fp/polyparse/)
> offers some lazy parsers, maybe one of those fits your needs.
> Text.ParserCombinators.Poly.StateLazy is the obvious candidate.

I have tried both Poly.StateLazy and Poly.State and they work quite well
- at least the space leak is eliminated. Now evaluation of the parser
state blows the stack...

The code is at http://hpaste.org/6310

Thanks in advance,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Space leak - help needed

2008-03-02 Thread Krzysztof Kościuszkiewicz
Dear Haskellers,

Another story from an (almost) happy Haskell user that finds himself
overwhelmed by laziness/space leaks.

I'm trying to parse a large file (>600MB) with a single S-expression
like structure. With the help of ByteStrings I'm down to 4min processing
time in constant space. However, when I try to wrap the parse results
in a data structure, the heap blows up - even though I never actually
inspect the structure being built! This bugs me, so I come here looking
for answers.

Parser follows:

> module Main where
> 
> import qualified Data.ByteString.Lazy.Char8 as B
> import Text.ParserCombinators.Parsec
> import Text.ParserCombinators.Parsec.Pos
> import System.Environment
> import System.Exit
> import qualified Data.Map as M
> import Lexer
> 
> type XdlParser a = GenParser Token XdlState a
> 
> -- Parser state
> type XdlState = Counts
> 
> type Counts = M.Map Count Integer
> 
> data Count = ListCount | SymbolCount
> deriving (Eq, Ord, Show)
> 
> emptyXdlState = M.empty
> 
> incCount :: Count -> (Counts -> Counts)
> incCount c = M.insertWith' (+) c 1
> 
> -- handling tokens
> myToken  :: (Token -> Maybe a) -> XdlParser a
> myToken test  = token showTok posTok testTok
> where
> showTok = show
> posTok  = const (initialPos "")
> testTok = test
> 
> -- Syntax of expressions
> data Exp = Sym !B.ByteString | List ![Exp]
> deriving (Eq, Show)
> 
> expr =  list <|> symbol
> 
> rparen = myToken $ \t -> case t of
> RParen  -> Just ()
> other   -> Nothing
> 
> lparen = myToken $ \t -> case t of
> LParen  -> Just ()
> other   -> Nothing
> 
> name = myToken $ \t -> case t of
> Name n -> Just n
> other  -> Nothing
> 
> list = do
> updateState $ incCount ListCount
> lparen
> xs <- many1 expr
> rparen
> return ()
> --  return $! (List xs)
> 
> symbol = do
> updateState $ incCount SymbolCount
> name >> return ()
> --  Sym `fmap` name
> 
> -- Top level parser
> top :: XdlParser XdlState
> top =  do
> l <- many1 list
> eof
> getState
> 
> main = do
> args <- getArgs
> case args of
> [fname] -> do
> text <- B.readFile fname
> let result = runParser top emptyXdlState fname (tokenize text)
> putStrLn $ either show show result
> _ -> putStrLn "usage: parse filename" >> exitFailure

And the Lexer:

> module Lexer (Token(..), tokenize) where
> 
> import qualified Data.ByteString.Lazy.Char8 as B
> import Control.Monad
> import Data.Char
> import Data.List
> import System.Environment
> import System.Exit
> 
> data Token = LParen
>| RParen
>| Name B.ByteString
> deriving (Ord, Eq, Show)
> 
> type Input = B.ByteString
> 
> -- Processor returns Nothing if it can't process the Input
> type Processor = Input -> Maybe ([Token], Input)
> 
> -- Tokenize ends the list when all processors return Nothing
> tokenize :: Input -> [Token]
> tokenize  = concat . unfoldr processAll
> where
> processors= [doSpaces, doComment, doParens, doName]
> processAll   :: Processor
> processAll bs = if B.null bs 
> then Nothing
> else foldr mminus Nothing $ map ($ bs) processors
> mminus a@(Just _) _ = a
> mminus Nothingb = b
> 
> doSpaces:: Processor
> doSpaces bs =
> if B.null sp
> then Nothing
> else Just ([], nsp)
> where
> (sp, nsp) = B.span isSpace bs
> 
> doComment:: Processor
> doComment bs =
> if B.pack "# " `B.isPrefixOf` bs
> then Just ([], B.dropWhile (/= '\n') bs)
> else Nothing
> 
> doParens :: Processor
> doParens bs  = case B.head bs of
> '(' -> Just ([LParen], B.tail bs)
> ')' -> Just ([RParen], B.tail bs)
> _   -> Nothing
> 
> doName   :: Processor
> doName  bs   =
> if B.null nsp
> then Nothing
> else Just ([Name nsp], sp)
> where
> (nsp, sp) = B.span (not . isRest) bs
> isRest c = isSpace c || c == ')' || c == '('

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] expanded standard lib

2007-11-20 Thread Krzysztof Kościuszkiewicz
On Tue, Nov 20, 2007 at 08:55:47AM +, Simon Peyton-Jones wrote:

> But we're just not sure how to do it:
>
> * What technology to use?
>
> * Matching up the note-adding technology with the existing
> infrastructure - GHC's user manual starts as XML and is generated into
> HTML by DocBook - In contrast, the library documentation is generated
> by Haddock.

I would advocate using a comment system that is similar to the one
at http://djangobook.com/. In terms of user manual comments might be
attached to sections and paragraphs in the document. Haddock already
generates HTML anchors for every type, variable and class, so these are
good candidates to attach user comments to.

> * Hardest of all: evolution.  Both GHC's user manual and library docs
> change every release.  Even material that doesn't change can get moved
> (e.g. section reorganisation).  We don't want to simply discard all
> user notes!  But it's hard to know how to keep them attached; after
> all they may no longer even be relevant.  They almost certainly don't
> belong in the source-code control system.

Comments in both html user guide and library docs could be easily
cross-referenced to specific parts of docbook/haskell source. The
remaining part (and I admit, labour intensive) would be to take the
notes into consideration while updating the documentation for the next
release. This doesn't happen too often (once a year? but if I'm wrong
please tell me) and I guess the whole point of accepting user's comments
is to improve the dock - that is to let writers address the issues in
the next version.

Now, examples illustrating use of library functions - that's a different
story...

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-17 Thread Krzysztof Kościuszkiewicz
Tim,

I have also enjoyed the article, it's well written and easy enough to
follow (at least for me).

Slightly offtopic - I am curious about the use of forall in some type
signatures:

> subsume :: forall p q r. Prop (p :=> q) -> Prop ((p :/\ q) :== p)
> subsume pIMPq = equivInj (impInj pq2p) (impInj p2pq)
>   where pq2p :: Prop (p :/\ q) -> Prop p
> pq2p assumePQ = andElimL assumePQ
> p2pq :: Prop p -> Prop (p :/\ q)
> p2pq assumeP = andInj assumeP q
>   where q = impElim assumeP pIMPq

There "r" type variable is mentioned, but it does not occur anywhere
else in the signature - what's the purpose of this construct?

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic choice of "reverse" implementation

2007-09-28 Thread Krzysztof Kościuszkiewicz
On Fri, Sep 28, 2007 at 04:38:35PM +0100, Brian Hulley wrote:

> > In my oppinion reversor would have type
> >  
> >> reversor :: (Foldable f) => [a] -> f b
> >>

> No, this is the wrong type. To find the correct type, if you look at the 
> type of the input argument in your code it will be the result of 
> (lines), so from ghci:
> 
> Prelude> :t lines
> lines :: String -> [String]
> Prelude>
> 
> Therefore (reverseor) has type [String] -> ???
> Now for the output type, you are using (output) as an input to (mapM_ 
> putStrLn). (mapM_) takes a list and uses its argument to do something to 
> each element of the list.

True. I forgot to mention imports in my code:

> import Prelude hiding (foldr, foldr1, reverse, mapM_)
> import System.Environment
> import Data.List hiding (foldr, foldr1)
> import Data.Foldable
> import Data.Traversable
> import Data.Sequence

So the type of mapM_ used in the code is
(Foldable t, Monad m) => (a -> m b) -> t a -> m ()

I'd like to keep the generic Foldable t there when "m" is specialized to IO.
I thought this would allow type of "reversor" to be specialized to
(Foldable f) => [String] -> f String

> For using Data.Sequence to implement reversor, all you need to do is 
> first convert [String] to Seq String, reverse the sequence, then convert 
> back from Seq String to [String].

Yes, probably that's how it works under the hood, but the reason I mentioned
Foldable is that I'd like to avoid [a] -> something -> [a], but keep the
type of output value from "reversor" abstract... For no particular reason,
just playing with this idea :)

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Dynamic choice of "reverse" implementation

2007-09-28 Thread Krzysztof Kościuszkiewicz
Fellow Haskellers,

I wanted to experiment a bit with lists and sequences (as in Data.List and
Data.Sequence), and I got stuck. I wanted to dynamically select processing
function depending on cmdline argument:

> main = do
> args <- getArgs
> let reversor = case args of
> ["sequence"] -> reverseList
> ["list"] -> reverseSeq
> _ -> error "bad args"
> input <- getContents
> let output = reversor $ lines $ input
> mapM_ putStrLn output

In my oppinion reversor would have type

> reversor :: (Foldable f) => [a] -> f b

but I couldn't get this to work. I've tried typeclass approach:

> class (Foldable f) => Reversor f where
> reverse' :: [a] -> f a
> 
> instance Reversor ([]) where
> reverse' = Data.List.reverse
> 
> instance Reversor ViewR where
> reverse' = viewr . foldr (<|) empty 
>
> reverseList = reverse' :: (???)
> reverseSeq  = reverse' :: (???)

but now in order to differentiate between "reverse'" functions I'd
have to provide different type annotations, and then "reversor" won't
typecheck...

Similar problem surfaced with this try:

> data Proc = SP | LP
> reverseList = reverse' LP
> reverseSeq = reverse' SP
>
> reverse' :: (Foldable f) => Proc -> [a] -> f a
> reverse' LP = Data.List.reverse
> reverse' SP = viewr . foldr (<|) empty

So now I'm looking for some suggestions how should I approach the
problem...

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clarification Please

2007-09-13 Thread Krzysztof Kościuszkiewicz
On Fri, Sep 14, 2007 at 03:45:02AM +0100, PR Stanley wrote:

> 5. Using merge, define a recursive function
> msort :: (Ord a) => [a] -> [a]
> that implements merge sort, in which the empty 
> list and singleton lists are already sorted, and 
> any other list is sorted by merging together the 
> two lists that result from sorting the two halves of the list separately. :
> Hint: first define a function
> ¬halve :: [a] -> [([a], [a])]
> ¬that splits a list into two halves whose length differs by at most one.

Split the input list using halve, sort both halves (as merge requires lists to
be sorted) and merge them into output list...

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: interaction between OS processes

2007-08-31 Thread Krzysztof Kościuszkiewicz
On Fri, Aug 31, 2007 at 11:31:38AM +0200, Andrea Rossato wrote:

> Thanks for your kind attention, but I don't think it's a matter of
> buffering (I indeed tried playing with hSetBuffering with no results).

That is because you need to change output buffering on both ends. I
don't know about haskell, but stdio says that handles to tty's are
line-buffered, stderr is not buffered and all other handles are fully
buffered. Of course you can flush the handles instead.

> Basically I'd like to write the equivalent of "expect", which talks to
> interactive programs (with the difference the mine is supposed to talk
> to a program I wrote, so I don't need to embed a domain specific
> language in it).

AFAIR expect uses pseudo-ttys (ptys) because in general one can't force
a program to change it's output buffering mode, so forcing it to talk to
a pair of terminals instead of fifos is used as a workaround.  Have a
look at pty(7).

Cheers,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange behavior of executeFile

2007-07-29 Thread Krzysztof Kościuszkiewicz
On Sun, Jul 29, 2007 at 10:34:10AM -0700, Bryan O'Sullivan wrote:

> GHC's file handles are backed by non-blocking file descriptors.  The 
> child process run by executeFile inherits the stdin, stdout and stderr 
> file descriptors of your Haskell process, so they're unexpectedly (from 
> its perspective) in non-blocking mode.
> 
> Due to POSIX sharing semantics, you can't simply switch those file 
> descriptors to blocking in the child, because they'll then become 
> blocking in the parent, too.

Yes, this would explain the behavior I'm seeing. My script neither forks
nor reads stdin, so I could hack around this problem by clearing the
O_NONBLOCK flag:

> setFdOption stdInput NonBlockingRead False

Thanks for your help!

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strange behavior of executeFile

2007-07-29 Thread Krzysztof Kościuszkiewicz
Fellow Haskellers,

I wrote a small script that intercepts arguments and exec's the pstops
program. The intention was to center and scale pages in a document
before processing it by psnup.

So far so good, I've ended up with something like:

> runPstops :: [Flag] -> IO ()
> runPstops flags =
>   do let args = mkArgs flags
>  when (isVerbose flags) $ do
>   hPutStrLn stderr $ "pstops " ++ unwords (map show args)
>  executeFile "pstops" True args Nothing

> main = do (opts, _) <- getOptions =<< getArgs
>   runPstops opts

This works for files, but "randomly" fails when stdin is connected to
a pipe (pstops complains that it can't seek input).  I've tested "raw"
pstops with pipes, files and /dev/null and it never fails, so I guess
there is something wrong with my code. Can anyone enlighten me in this
matter? :)

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Phone IRL: +353851383329,  Phone PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-07-20 Thread Krzysztof Kościuszkiewicz
On Thu, Jul 19, 2007 at 11:39:26PM -0400, Ronald Guida wrote:

> In Problem 11, a 20x20 grid of numbers is given, and the problem is to
> find the largest product of four numbers along a straight line in the
> grid.  The line can be horizontal, vertical, or diagonal.

I found it easier to work with Arrays in this example:

> > grid :: [[Integer]]
> > grid = readGrid gridText

> gridArr :: [[Integer]] -> Array (Int, Int) Integer
> gridArr = array ((0, 0), (19, 19))

Then you can define a handy function for extracting whatever combination of
indices you need:

> extractBy :: (Ix i, Ord a) => ((i, e) -> a) -> Array i e -> [[e]]
> extractBy f = 
>   map (map snd) . groupBy (equals f) . sortBy (comparing f) . assocs

And from there on you can work your way out of this problem by replacing
??? with functions that map ((i, j), v) to some value common for same
row, col, or diagonal:

> rows = extractBy ???
> cols = extractBy ???
> diags = extractBy ???
> adiags = extractBy ???

> > makeGroups :: Int -> [a] -> [[a]]
> > makeGroups 0 _ = []
> > makeGroups n xs = let ys = take n xs in
> >  if n == length ys
> >then ys : (makeGroups n $ tail xs)
> >else []

The above can be shortened to:

> makeGroupsOf n = map (take n) . tails

>From here on you should be able to compute products of whatever is required.
Good luck and have fun!

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Phone IRL: +353851383329,  Phone PL: +48783303040
"Simplicity is the ultimate sophistication" -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe