Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-25 Thread Stephan Friedrichs
Henning Thielemann wrote:
 [...]
 
 http://haskell.org/haskellwiki/Case

Maybe we (i. e. someone with a wiki account ;) ) should add Jeremy's
proposal - using let and guards - to the page (under section 2.2,
syntactic suger)? IMHO this is much clearer than case () of _.

foo =
let x | 1  1 = uh-oh
  | otherwise = all is well
in x

Regards,
Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-25 Thread Luke Palmer
On Wed, Jun 24, 2009 at 11:13 PM, Hector Guilarte hector...@gmail.comwrote:


 Thanks! Actually,  if I understood well what you proposed, that's how I
 first tought of doing it, but with a [Maybe String] and only append whenever
 I actually had a (Just string), but as I said before, I don't think my
 teacher is gonna like that solution since it is not going to print when the
 interpreter finds the show instruction in the GCL code, it is gonna wait
 until it finishes to interpret the whole code and then print everything.


Not true!  Haskell is lazy.  You just have to think about program evaluation
inside out.  So it's not print *when* you come across this instruction,
but rather run the program just far enough to print the first line.

That's would be ok with me, but actually in a language point of view that
 wouldn't be to usefull, since trying to debug a program printing flags
 couldn't be done (and I'm not doing a debbuger for it). I know my language
 is not gonna be used for real, but I'm sure that would be my teacher's
 argument to tell me I can't do it that way. Still, I sent him an e-mail
 asking if it can be done like that just in case.


I assume that Haskell is *your* language choice, not the teacher's.  In
which case it may be very hard to convince the teacher that this is correct,
if he is used to thinking in an imperative style.  Nonetheless, you chose a
functional language and it is only fair to solve the program in a functional
way, right?  Haskell tries to be a language with *no* side effects at all,
it just accidentally falls short here and there; if it achieves its goal,
there would be *no* correct way to solve it by your alleged teacher's
argument.



 If I didn't understand what you said, can you explain it again please?


I think you've got it, except for the understanding that lists are lazy so
running the program is equivalent to asking for elements from the list.



 If I did then, does anybody knows how to print on the screen in the moment
 the show instruction is interpreted that guarantees that my code is gonna be
 safe


That is a very hard thing to ask of a pure language, which does not really
concern itself with such questions.  The moment the show instruction is
interpreted is abstracted away from the Haskell programmer, so that the
compiler may choose to evaluate it any time it pleases (as long as it gives
you the answer you asked for).


 Also, nobody has told me why I shouldn't just use my original solution
 using unsafePerformIO, is it really bad? is it dangerous? why is it
 unsafe?


It is contrary to the spirit of Haskell, and breaks invariants that
reasoning in the language relies on.  It is not technically dangerous,
i.e. your program will still work, but you will be contested here and
there about whether it should be considered correct.  If you published a
Haskell module which used such a trick to the community, you would have a
very hard time convincing people to use it.

The invariant it breaks is called referential transparency, or maybe
purity (those terms are kind of muddled together the way I look at
things).  Either way, consider the following program:

mult2 x = 2*x
main = do
print (mult2 21)
print (mult2 21)

Now, functions are in the mathematical sense in Haskell, so the result of a
function is *entirely* determined by its arguments.  That means, without
considering anything about the definition of mult2, refactor main into:

main = do
let answer = mult2 21
print answer
print answer

And we *know* that this program will behave exactly the same.

However, if mult2 were instead:

mult2 x = unsafePerformIO $ do { print x; return (2*x) }

Then the former program would probably print 21,42,21,42,  whereas the
latter would print 21,42,42.  Thus our *correct* transformation of programs
changed behavior.

Haskell programmers rely on this sort of refactoring all the time, and
unsafePerformIO has the potential to break it.  That is why it's unsafe.

Safe uses of unsafePerformIO are those where any such transformation won't
change the overall behavior of the program.  They do exist, and are usually
employed for optimization purposes.  But yours is not such a case; your
unsafePerformIO has observable side-effects.

The list of strings solution is *the* Haskell way to solve this problem.
If your teacher does not accept the solution, then your teacher is not
actually letting you program in Haskell.

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


Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-25 Thread minh thu
2009/6/25 Hector Guilarte hector...@gmail.com:


 On Fri, Jun 26, 2009 at 12:58 AM, Brandon S. Allbery KF8NH
 allb...@ece.cmu.edu wrote:

 On Jun 26, 2009, at 00:43 , Hector Guilarte wrote:

 Thanks! Actually,  if I understood well what you proposed, that's how I
 first tought of doing it, but with a [Maybe String] and only append whenever
 I actually had a (Just string), but as I said before, I don't think my
 teacher is gonna like that solution since it is not going to print when the
 interpreter finds the show instruction in the GCL code, it is gonna wait
 until it finishes

 I think maybe you don't quite have a grasp of lazy evaluation yet.  Try
 it.

 Also, nobody has told me why I shouldn't just use my original solution
 using unsafePerformIO, is it really bad? is it dangerous? why is it
 unsafe?

 You were told earlier:

 Well, writing to the standard output is certainly a side effect. (This
 does not mean that you cannot use unsafePerformIO. The compiler,
 however, may assume that any value is free from side effects. This
 means
 that you could get, in theory, less or more output from your program
 than you want. In this sense it is not safe.)

 Because pure (i.e. non-IO) values by definition never change, the compiler
 is free to assume that it can do them exactly once and remember the result.
  This means that it is possible for the compiler to evaluate your
 unsafePerformIO once and never again... or, more likely, to notice that the
 pure result is always () (because unsafePerformIO hides the IO from the
 compiler) and optimize it away completely (the do it exactly once being at
 compile time instead of run time).

 Ok, I got it this time, thanks! I should really talk this with my teacher.
 I'll post whatever he tells me... Let's hope he lets me just acumulate all
 the strings and print them in the end.

Hi Hector,

The notion you have about print in the end or (in a previous mail)
print as soon as it is evaluated is wrong.

Haskell is lazy.

This means things are evaluted when they are needed. Here, this means
the strings are produced *because* you print them out. If you don't
print them (or use them in another needed computation), they won't be
evaluated.

Also, garbage collection will reclaim the memory used by the strings
already evaluated and printed, so the accumulation doesn't really
occur from a memory usage point of view.

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


Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-25 Thread Brandon S. Allbery KF8NH

On Jun 26, 2009, at 01:11 , Hector Guilarte wrote:
Ok, I got it this time, thanks! I should really talk this with my  
teacher. I'll post whatever he tells me... Let's hope he lets me  
just acumulate all the strings and print them in the end.



You're still missing what lazy evaluation means.  If you write the  
equivalent of


  while x := read line do
mylist = mylist ++ x
  done
  result = process mylist -- this is the accumulate all the strings  
part.. except it isn't

  for x in result do
print x
  done

what you get is actually something like

  while x := read line do
print (process [x])
  done

This is because of laziness:  each part of the program requests only  
the minimum that is needed at any given time, and execution is  
interleaved as necessary.  You can think of it as:  print x requires  
a single item x, so it steps through process until a single item  
is produced; process then steps through the while read until it  
gets enough information to produce that single item being demanded at  
the moment.  How much depends on what process actually does:  if,  
for example, it's adding 1 to each item in the list, then it only  
needs to do 1 iteration of the while read in order to get something  
to add 1 to and pass on to the print x that is demanding an item  
from it.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in array index.

2009-06-25 Thread Claus Reinke

 It's too bad that indexes are `Int` instead of `Word` under
 the hood. Why is `Int` used in so many places where it is
 semantically wrong? Not just here but also in list indexing...
 Indices/offsets can only be positive and I can't see any good
 reason to waste half the address space -- yet we encounter
 this problem over and over again.


Readers who disliked the above also disliked the following:

   index out of range error message regression
   http://hackage.haskell.org/trac/ghc/ticket/2669

   Int / Word / IntN / WordN are unequally optimized
   http://hackage.haskell.org/trac/ghc/ticket/3055

   Arrays allow out-of-bounds indexes
   http://hackage.haskell.org/trac/ghc/ticket/2120
   ..

Not to mention that many serious array programmers use their
own array libraries (yes, plural:-(, bypassing the standard, so 
their valuable experience/expertise doesn't result in improvements 
in the standard array libraries (nor have they agreed on a new API). 

If any of this is affecting your use of GHC or libraries, you might 
want to add yourself to relevant tickets, or add new tickets. Small
bug fixes, alternative designs and grand array library reunification 
initiatives might also be welcome.


Claus

PS. You could, of course, rebase your array indices to make
   use of the negatives, so the address space isn't wasted, just
   made difficult to use.


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


Re[2]: [Haskell-cafe] Error in array index.

2009-06-25 Thread Bulat Ziganshin
Hello Claus,

Thursday, June 25, 2009, 11:50:12 AM, you wrote:

 PS. You could, of course, rebase your array indices to make
 use of the negatives, so the address space isn't wasted, just
 made difficult to use.

no, he can't - internally indexes are always counted from 0, so array
cannot have more than 2g-1 elements

i think the best he can do is to write his own ArraOfBool
implementation with Word indices


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-25 Thread Ketil Malde
Luke Palmer lrpal...@gmail.com writes:

 mult2 x = unsafePerformIO $ do { print x; return (2*x) }

 main = do
 let answer = mult2 21
 print answer
 print answer

 [this] would print 21,42,42.  Thus our *correct* transformation of programs
 changed behavior.

Just to expand a bit on this, if you now enable optimization, the
compiler might decide that mult2 is a small function and just inline
it, essentially turning the program back into the first version (which
I didn't quote).

So the output of your program also may depend on the compiler and
compiler switches you use - this too is frowned upon in the ivory
towers of functional programming. 

 Safe uses of unsafePerformIO are those where any such transformation won't
 change the overall behavior of the program.  They do exist

Debug.Trace.trace is, I guess, the most well-known example?  Which you might
even consider using here, since at least the library will try to
instruct the compiler not to inline, so it's somewhat less likely to
do unexpected things.

 The list of strings solution is *the* Haskell way to solve this problem.
 If your teacher does not accept the solution, then your teacher is not
 actually letting you program in Haskell.

...which would come as no big surprise.

I'm told that my old alma mater, the informatics department at the
University of Bergen, is now going to teach Haskell as a small part of
a small course titled programming paradigms or some such this fall.
Haskell FTW! (Or more like Haskell 1 - Java 9311, but still.)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code walking off the right edge of the screen

2009-06-25 Thread Alberto G. Corona
What about extending haskell (or ghc) with mixfix operators, Agda style?. At
first sigth it would permit the creation of custom control structures and
perhaps more readable DSLs.

2009/6/25 Stephan Friedrichs deduktionstheo...@web.de

 Henning Thielemann wrote:
  [...]
 
  http://haskell.org/haskellwiki/Case

 Maybe we (i. e. someone with a wiki account ;) ) should add Jeremy's
 proposal - using let and guards - to the page (under section 2.2,
 syntactic suger)? IMHO this is much clearer than case () of _.

 foo =
let x | 1  1 = uh-oh
  | otherwise = all is well
in x

 Regards,
 Stephan

 --

 Früher hieß es ja: Ich denke, also bin ich.
 Heute weiß man: Es geht auch so.

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

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


[Haskell-cafe] How to fork a process?

2009-06-25 Thread Magicloud Magiclouds
Hi,
  In many language, both thread and process are supported. But in
haskell's document, the only thing I could find called fork is to make
a thread. So how to fork the program itself, like fork () in C?
  Thanks.
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fork a process?

2009-06-25 Thread Brandon S. Allbery KF8NH

On Jun 25, 2009, at 05:01 , Magicloud Magiclouds wrote:

 In many language, both thread and process are supported. But in
haskell's document, the only thing I could find called fork is to make
a thread. So how to fork the program itself, like fork () in C?



Internal threads can be done reasonably portably (well, assuming you  
don't look at the internals of the runtime :) but fork() is specific  
to POSIX/Unix-like systems.  (I'm told you can emulate it on Windows  
but it's neither fast nor easy; on most non-Unixlike systems the  
native operation is to spawn a process running a new executable, and  
cloning the current process is unusual at best.)


As such, forkProcess lives in System.Posix.Process, along with  
executeFile (overlaying the current process's executable image is  
likewise a Unixism) and other operations specific to the POSIX/Unix- 
like process model.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] combining monads with IO

2009-06-25 Thread Richard Silverman


Hi all,

I'm puzzled by something. Suppose I have some code that does lots of 
IO, and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* 
ugly -- the code is littered with lift functions!  Is there no cleaner 
way to do this?


Thanks,

- Richard

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


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Martijn van Steenbergen

Richard Silverman wrote:
I'm puzzled by something. Suppose I have some code that does lots of IO, 
and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* ugly 
-- the code is littered with lift functions!  Is there no cleaner way to 
do this?


Not that I know of. However, you can usually group IO-statements 
together in one bigger block:


blah = do
  foo - ask
  biz - liftIO $ do
meep
bop foo
bleep foo
  zap biz

etc.

And if there is a limited number of specific functions you need to lift 
often, you can write generalised MonadIO-based versions of these so that 
you can call them directly from the monad transformer:


  getLine :: MonadIO m = m String
  getLine = liftIO SystemIO.getLine

Assuming an appropriate MonadIO instance of ReaderT, of course.

Does that help?

Martijn.

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


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Matthias Görgens
By the way, how would one write the following with Monad Transformers?

 newtype IOMayfail a = IOMayfail (IO (Maybe a))

 instance Monad IOMayfail where
 return = IOMayfail . return . return
 (=) a f = IOMayfail (bind (run a) (run . f))
 fail s = trace s (IOMayfail $ return Nothing)

 run :: IOMayfail a - IO (Maybe a)
 run (IOMayfail a) = a

 bind :: IO (Maybe a) - (a - IO (Maybe b)) - IO (Maybe b)
 bind a f = do r - a
   case r of Nothing - return Nothing
 Just r' - f r'
 Lift :: IO a - IOMayfail a
 lift f = IOMayfail (f = return . return)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov

Well, without fail part:

newtype IOMayfail a = IOMayfail (MaybeT IO a) deriving Monad

Matthias Görgens wrote on 25.06.2009 17:14:

By the way, how would one write the following with Monad Transformers?


newtype IOMayfail a = IOMayfail (IO (Maybe a))



instance Monad IOMayfail where
return = IOMayfail . return . return
(=) a f = IOMayfail (bind (run a) (run . f))
fail s = trace s (IOMayfail $ return Nothing)



run :: IOMayfail a - IO (Maybe a)
run (IOMayfail a) = a



bind :: IO (Maybe a) - (a - IO (Maybe b)) - IO (Maybe b)
bind a f = do r - a
  case r of Nothing - return Nothing
Just r' - f r'
Lift :: IO a - IOMayfail a
lift f = IOMayfail (f = return . return)

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


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


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Matthias Görgens
Thanks.  Can I add something like fail?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread Matthias Görgens
I have a program that optimizes train schedules.  It employs an
external solver for Integer Linear Programs.  The solve function has
the following type:

 solve :: Constraints - IO (Maybe Solution)

And this works.  However, my external solver also behaves like a pure
function from input to output.  I wonder whether this guarantee should
be reflected in the type system.  I'd also appreciate if the compiler
would be able to eliminate some calls to the solver.

 solvePure :: Constraints - Maybe Solution
 solvePure = unsafePerformIO . solve

Is this a good idea?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread Jochem Berndsen
Matthias Görgens wrote:
 I have a program that optimizes train schedules.  It employs an
 external solver for Integer Linear Programs.  The solve function has
 the following type:
 
 solve :: Constraints - IO (Maybe Solution)
 
 And this works.  However, my external solver also behaves like a pure
 function from input to output.  I wonder whether this guarantee should
 be reflected in the type system.  I'd also appreciate if the compiler
 would be able to eliminate some calls to the solver.
 
 solvePure :: Constraints - Maybe Solution
 solvePure = unsafePerformIO . solve
 
 Is this a good idea?

This is safe as long as there are no side effects, and not depend on its
environment (e.g. don't open files, read from environment variables).

In general, functions that do not IO should not have IO in their type
signature, because this will contaminate calling functions unnecessarily.

Adding 'unsafePerformIO' will work, but a better idea might be to
understand why your solver has IO in its type signature. Is this because
of FFI calls? You can remove IO in FFI calls if they are free from side
effects as well.

Regards,

-- 
Jochem Berndsen | joc...@functor.nl
GPG: 0xE6FABFAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov

Sure:

newtype IOMayfail a = IOMayfail {runIOMayfail :: MaybeT IO a}

instance Monad IOMayfail where
  return = IOMayfail . return
  IOMayfail m = f = IOMayfail $ m = runIOMayfail . f
  fail = whatever you like

Matthias Görgens wrote on 25.06.2009 17:28:

Thanks.  Can I add something like fail?

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


Re: [Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread John Meacham
On Thu, Jun 25, 2009 at 03:38:41PM +0200, Matthias Görgens wrote:
 I have a program that optimizes train schedules.  It employs an
 external solver for Integer Linear Programs.  The solve function has
 the following type:
 
  solve :: Constraints - IO (Maybe Solution)
 
 And this works.  However, my external solver also behaves like a pure
 function from input to output.  I wonder whether this guarantee should
 be reflected in the type system.  I'd also appreciate if the compiler
 would be able to eliminate some calls to the solver.
 
  solvePure :: Constraints - Maybe Solution
  solvePure = unsafePerformIO . solve
 
 Is this a good idea?

If it is actually fully pure, including things like debugging output,
then this is fine. However, if the algorithm takes a signifigant amount
of time or resources, you may want to keep it in IO just so users can
have control over exactly when and how often it is run. 

unsafePerformIO was included in the FFI spec for just this sort of case.

John

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


Re: [Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread Max Rabkin
On Thu, Jun 25, 2009 at 3:49 PM, John Meachamj...@repetae.net wrote:
 However, if the algorithm takes a signifigant amount
 of time or resources, you may want to keep it in IO just so users can
 have control over exactly when and how often it is run.

If you had a pure function written in Haskell that used a lot of time
and memory, would you put it in IO just so users can have control over
exactly when and how often it is run?

bigFatFunction :: Foo - IO Bar
bigFatFunction x = return . bigFatFunction $ x

If the function really does use a lot of time and memory and your
compiler is duplicating calls to it, then you have a pessimizing
compiler and should file a bug.

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


Re: [Haskell-cafe] Another question about unsafePerformIO

2009-06-25 Thread Matthias Görgens
 Adding 'unsafePerformIO' will work, but a better idea might be to
 understand why your solver has IO in its type signature. Is this because
 of FFI calls? You can remove IO in FFI calls if they are free from side
 effects as well.

My solver has IO in the type signature, because I said so. :o)  The
solve function is defined like this:

 solve :: Constraints - IOMayfail Solution
 solve constraints = do { solString - scip (genZimpl constraints);
parseSol nfnrs solString;}

 scip :: String - IOMayfail String
 scip zimplCode = do {lift $ writeFileAtomic zplFile zimplCode;
 exitCode - lift $ system (command zplFile solFile);
 case exitCode of ExitSuccess - lift (readFile solFile)
  ExitFailure n - fail (Calling Scip 
 failed with code ++ show n ++.\n);}

 command inFile outFile = ./scip -c 'read \ ++ inFile ++\' -c 'optimize' 
  ++-c 'write solution \++outFile++\' -c 'quit'

(I added {}; because I some mail clients use variable width fonts and
mess up layout. Eg mine does.)

The solver SCIP also offers a FFI interface.  But I was too lazy to
use that, yet.  So I use a temp-file (which should really use
openTempFile instead of a fixed name) for communication.

So because of my lazyness there are still things in it that look like
side-effects, but they are not so in principal.  (Also I am the only
user of my code, so I can get away with deferring true FFI.)

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


[Haskell-cafe] Can you determine a constructor's arity using Data.Typeable and Data.Data?

2009-06-25 Thread David Fox
Is it possible to determine the arity of a value's constructor?
Suppose I have a value x of type

  data A = B Int | C

They typeOf function returns its TypeRep, which contains its type
constructor, but I don't see how to decide whether that
constructor's arity is 0 or 1.  If the type has field names
I can look at those using Data.Data.conFields and count them,
but if it doesn't I don't see how to do it.

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


[Haskell-cafe] Hack (web) and apache configuration

2009-06-25 Thread Henry Laxen
Dear Group,

I am posting this here even though it probably belongs on the
apache list because I suspect other haskell users will be able to
find it here more easily.  I am playing around with hack, and am
having trouble with configuring apache with fastcgi to make
things work.  My understanding of the hack concept is that it
provides a stardardized interface that lets you glue together
web Applications.  It also provides several front-ends, such as
happs, and fastcgi etc.  Now based on looking at the Middleware
supplied with hack, it seems to be trying to dispatch based on
the contents of the pathInfo field of the Env record.  So, my
question is, how do we configure Apache2 with the fastcgi handler
so that something appears in the pathInfo field?

I have tried several things, the most recent being:

RewriteEngine on
RewriteRule ^/(.*)$ /hackTest?input=$1 [T=application/x-httpd-cgi]
Location /
SetHandler fastcgi-script
Options ExecCGI FollowSymLinks
/Location

but the pathInfo field is always null.  

Env {requestMethod = GET, scriptName = /lambda, pathInfo = , 
queryString = input=lambda, serverName = 127.0.0.1, serverPort = 80, 
http = [(FCGI_ROLE,RESPONDER),(SCRIPT_URL,/lambda),
(SCRIPT_URI,http://127.0.0.1/lambda;),(User-Agent,curl/7.18.2 
(x86_64-pc-linux-gnu) libcurl/7.18.2 OpenSSL/0.9.8g zlib/1.2.3.3 libidn/1.8
libssh2/0.18),
(Host,127.0.0.1),(Accept,*/*),(PATH,/usr/local/bin:/usr/bin:/bin),
(SERVER_SIGNATURE,addressApache/2.2.9 (Debian) mod_fastcgi/2.4.6
proxy_html/3.0.0 mod_apreq2-20051231/2.6.0 mod_perl/2.0.4 Perl/v5.10.0 Server at
127.0.0.1 Port 80/address\n),
(SERVER_SOFTWARE,Apache/2.2.9 (Debian) mod_fastcgi/2.4.6 proxy_html/3.0.0
mod_apreq2-20051231/2.6.0 mod_perl/2.0.4 Perl/v5.10.0),
(SERVER_NAME,127.0.0.1),(SERVER_ADDR,127.0.0.1),
(SERVER_PORT,80),(REMOTE_ADDR,127.0.0.1),
(DOCUMENT_ROOT,/home/henry/maztrave2/www/fcgi),
(SERVER_ADMIN,[no address given]),
(SCRIPT_FILENAME,/home/henry/maztrave2/www/fcgi/hackTest),
(REMOTE_PORT,44936),
(GATEWAY_INTERFACE,CGI/1.1),(SERVER_PROTOCOL,HTTP/1.1),
(REQUEST_METHOD,GET),(QUERY_STRING,input=lambda),
(REQUEST_URI,/lambda),(SCRIPT_NAME,/lambda)], 
hackVersion = [2009,5,19], hackUrlScheme = HTTP, hackInput = Empty, hackErrors =
HackErrors, hackHeaders = []}% 


I think what I want is to have all URLS, such as:

http://127.0.0.1/lambda

be dispatched though my hackTest executable, without having to go
through the rewrite, but I can't convice apache to do that.  In
the interest of completeness, my hackTest.hs file is the
following:

import Hack
import Hack.Handler.FastCGI
import Data.ByteString.Lazy.Char8 (pack)
import Hack.Contrib.Middleware.Lambda

app :: Application
app = \env -   return $ Response
{ status  = 200
, headers = [ (Content-Type, text/plain) ]
, body= pack $ show env
}

main = runFastCGIorCGI $ lambda app

--

One final comment to the authors of hack.  Would you please
consider renaming this project.  hack is such a common word that
has nothing to do with this project that it make searching the
web with google, etc. almost useless.  I realize it is a clever
respelling of the ruby version rack, but please consider naming
it something more unique, while it is still relatively new on the
web.

Thanks in advance for your help.
Best wishes,
Henry Laxen


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


[Haskell-cafe] Using unsafePerformIO safely

2009-06-25 Thread gladstein
Regarding how to make the show instructions cause printout as soon as
they are executed:

If you write your interpreter to return a list of printout lines
(strings), you get this behavior for free. Haskell's laziness enables
the printing to start right away, while in an imperative language the
list of strings wouldn't be returned until it was complete.

To see this in action, try this program:

main = mapM putStrLn myList

myList = [first, second, loop, third]

loop = loop 

Despite the infinite loop, first and second print out.

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


Re: [Haskell-cafe] Can you determine a constructor's arity using Data.Typeable and Data.Data?

2009-06-25 Thread José Pedro Magalhães
Hey David,

For instance:

arity :: (Data a) = a - Int
 arity = length . gmapQ (const ())



Cheers,
Pedro

On Thu, Jun 25, 2009 at 17:31, David Fox dds...@gmail.com wrote:

 Is it possible to determine the arity of a value's constructor?
 Suppose I have a value x of type

   data A = B Int | C

 They typeOf function returns its TypeRep, which contains its type
 constructor, but I don't see how to decide whether that
 constructor's arity is 0 or 1.  If the type has field names
 I can look at those using Data.Data.conFields and count them,
 but if it doesn't I don't see how to do it.

 -david


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


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


Re: [Haskell-cafe] [ANN] full-sessions: yet another implementation of session types

2009-06-25 Thread Jason Dusek
  Is there a relationship between sessions and coroutines?

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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread Wei Hu
Could you or anyone else briefly explain how mmtl solves the
combinatorical explosion problem? Reading the source code is not very
productive for newbies like me. Thanks!

On Tue, Jun 23, 2009 at 5:34 AM, Luke Palmerlrpal...@gmail.com wrote:
 On Tue, Jun 23, 2009 at 2:20 AM, papa.e...@free.fr wrote:

  Simple: the definition of MonadState uses those extensions.

 Thanks, yes it helps and explains all. :^)

 I suppose then that if -XFlexibleContexts is indeed required by the
 standard libraries, it is a safe extension, meaning supported by all
 compilers? Are many such extensions de-facto standard that anyone can enable
 by default?

 Now to answer your question, with 50% less idealistic ranting!
 There is definitely a canon of safe extensions in the community.
  Hierarchical libraries (that's not even an -X flag, it's just on),
 multiparam typeclasses, fundeps are among them.  I can't say whether
 FlexibleContexts is.
 However, your question is rather moot here, as you are using the mtl.  It
 uses UndecidableInstances, whose blessing into the de facto standard would
 require as a precondition the batshit-insanity of the de facto community.
 I personally use transformers as my monad library, as it is (as far as I
 know) the only Haskell 98 monad library on Hackage (you'll hardly notice the
 more explicit lifts, I promise!).  However, looking a bit more
 optimistically into the future, I'd say mmtl is the most likely to
 succeed, since it solves the combinatorical explosion problem which haunts
 all the other monad libraries (and at least avoids the extensions which are
 doomed to failure).
 Anyway, it is never too early to free yourself of mtl.  Look at the monad
 libraries on hackage and weigh their pros and cons; the only thing special
 about mtl is its mediocrity.
 Luke
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread Wei Hu
OK, I found two papers by the author, Mauro Jaskelioff, that seem
relevant. One paper Modular Monad Transformers is all category
theoretical. Maybe I should read the other one Monatron: An
Extensible Monad Transformer Library.

On Thu, Jun 25, 2009 at 12:17 PM, Wei Huwei@gmail.com wrote:
 Could you or anyone else briefly explain how mmtl solves the
 combinatorical explosion problem? Reading the source code is not very
 productive for newbies like me. Thanks!

 On Tue, Jun 23, 2009 at 5:34 AM, Luke Palmerlrpal...@gmail.com wrote:
 On Tue, Jun 23, 2009 at 2:20 AM, papa.e...@free.fr wrote:

  Simple: the definition of MonadState uses those extensions.

 Thanks, yes it helps and explains all. :^)

 I suppose then that if -XFlexibleContexts is indeed required by the
 standard libraries, it is a safe extension, meaning supported by all
 compilers? Are many such extensions de-facto standard that anyone can enable
 by default?

 Now to answer your question, with 50% less idealistic ranting!
 There is definitely a canon of safe extensions in the community.
  Hierarchical libraries (that's not even an -X flag, it's just on),
 multiparam typeclasses, fundeps are among them.  I can't say whether
 FlexibleContexts is.
 However, your question is rather moot here, as you are using the mtl.  It
 uses UndecidableInstances, whose blessing into the de facto standard would
 require as a precondition the batshit-insanity of the de facto community.
 I personally use transformers as my monad library, as it is (as far as I
 know) the only Haskell 98 monad library on Hackage (you'll hardly notice the
 more explicit lifts, I promise!).  However, looking a bit more
 optimistically into the future, I'd say mmtl is the most likely to
 succeed, since it solves the combinatorical explosion problem which haunts
 all the other monad libraries (and at least avoids the extensions which are
 doomed to failure).
 Anyway, it is never too early to free yourself of mtl.  Look at the monad
 libraries on hackage and weigh their pros and cons; the only thing special
 about mtl is its mediocrity.
 Luke
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



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


Re: [Haskell-cafe] Hack (web) and apache configuration

2009-06-25 Thread Anton van Straaten

Henry Laxen wrote:

I have tried several things, the most recent being:

RewriteEngine on
RewriteRule ^/(.*)$ /hackTest?input=$1 [T=application/x-httpd-cgi]
Location /
SetHandler fastcgi-script
Options ExecCGI FollowSymLinks
/Location

but the pathInfo field is always null.  


Path info is path-like data that directly follows the name of the 
resource being referenced, e.g.: /myfiles/foo.html/this/is/path/info


A rule that would give you path info in the case you describe would be 
more like this:


  RewriteRule ^/(.*)$ /hackTest/$1 [T=application/x-httpd-cgi]

Whether that works depends on how /hackTest is being dispatched, but if 
Hack expects pathinfo, then it may just work.


Anton

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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread David Menendez
On Thu, Jun 25, 2009 at 12:17 PM, Wei Huwei@gmail.com wrote:
 Could you or anyone else briefly explain how mmtl solves the
 combinatorical explosion problem? Reading the source code is not very
 productive for newbies like me. Thanks!

It's a good question, since from what I can tell mmtl does not solve
the problem.

Some quick background: If you have M monad transformers and N classes
of operations, you normally need M*N instance declarations, i.e., one
per transformer per class. Each instance either provides the
functionality directly, such as the MonadState instance for StateT, or
promotes it from the underlying monad, such as the MonadState instance
for ReaderT.

mmtl instead provides 2*M instances. For each transformer, it has one
direct instance (such as MonadState (StateT s m)) and one instance
which promotes through any transformer (such as MonadState (t (StateT
s m))).

The problem is that this limits you to using at most two transformers
at a time. For example, the type ErrorT String (ReaderT Int (StateT
Int m)) is an instance of MonadError and MonadReader, but not
MonadState because it doesn't have the form t (StateT s m).

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can you determine a constructor's arity using Data.Typeable and Data.Data?

2009-06-25 Thread David Fox
Oh, that make sense!

2009/6/25 José Pedro Magalhães j...@cs.uu.nl

 Hey David,

 For instance:

 arity :: (Data a) = a - Int
 arity = length . gmapQ (const ())



 Cheers,
 Pedro

 On Thu, Jun 25, 2009 at 17:31, David Fox dds...@gmail.com wrote:

 Is it possible to determine the arity of a value's constructor?
 Suppose I have a value x of type

   data A = B Int | C

 They typeOf function returns its TypeRep, which contains its type
 constructor, but I don't see how to decide whether that
 constructor's arity is 0 or 1.  If the type has field names
 I can look at those using Data.Data.conFields and count them,
 but if it doesn't I don't see how to do it.

 -david


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



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


[Haskell-cafe] Re: Hack (web) and apache configuration

2009-06-25 Thread Henry Laxen

Anton van Straaten anton at appsolutions.com writes:

 Path info is path-like data that directly follows the name of the 
 resource being referenced, e.g.: /myfiles/foo.html/this/is/path/info
 
 A rule that would give you path info in the case you describe would be 
 more like this:
 
RewriteRule ^/(.*)$ /hackTest/$1 [T=application/x-httpd-cgi]
 
 Whether that works depends on how /hackTest is being dispatched, but if 
 Hack expects pathinfo, then it may just work.
 
 Anton
 

Dear Anton,

Thank you, that works perfectly.  That's what I love about programming, just
change a single character, and the world goes from total chaos to perfect order.
 It reminds me of a saying I heard once.  If carpenters built houses the way
programmers write programs, you could walk into any house, remove any single
nail, and the structure would collapse into pieces no larger than toothpicks.

Thanks again.
Henry




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


Re: [Haskell-cafe] Parsing .dot files?

2009-06-25 Thread Neil Mitchell
Hi

I have some code, but never got round to uploading it or turning it in
to a package. If the graphviz package doesn't have what you want I'm
happy to give you a copy. (I would attach the code but I don't have it
on this machine)

Thanks

Neil

On Wed, Jun 24, 2009 at 7:38 AM, minh thunot...@gmail.com wrote:
 2009/6/24 Lee Pike leep...@gmail.com:
 Hi,

 Does anybody know of a Haskell library for parsing .dot graph files?  (I
 know Andy Gill wrote dotgen for *generating* .dot files
 http://hackage.haskell.org/package/dotgen.)

 Hi,

 You might be interested in http://hackage.haskell.org/package/graphviz.

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

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


[Haskell-cafe] Re: Hack (web) and apache configuration

2009-06-25 Thread Simon Michael

harack ? *Harack*. Excuse me.

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


Re: [Haskell-cafe] Haskell on JVM

2009-06-25 Thread Jason Dusek
2009/06/24 Greg Meredith lgreg.mered...@biosimilarity.com:
 Better support for std Haskell syntax

  What does this mean, actually? Better support for standard
  Haskell syntax than what?

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


Re: [Haskell-cafe] unique identity and name shadowing during type inference

2009-06-25 Thread Geoffrey Irving
Thanks.  I'll go with the monad for now.

Geoffrey

On Sat, Jun 20, 2009 at 4:40 PM, Lennart
Augustssonlenn...@augustsson.net wrote:
 Use 1.  You'll probably need a monad in the type checker soon or later
 anyway, e.g., for handling errors.

On Sun, Jun 21, 2009 at 5:13 AM, Zsolt Dollensteinzsol.z...@gmail.com wrote:
 I think you should also take a look at the value-supply package. At least
 that was my solution for scope analysis issues.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell on JVM

2009-06-25 Thread Greg Meredith
Jason,

CAL's syntax is not std Haskell syntax.

Best wishes,

--greg

On Thu, Jun 25, 2009 at 11:10 AM, Jason Dusek jason.du...@gmail.com wrote:

 2009/06/24 Greg Meredith lgreg.mered...@biosimilarity.com:
  Better support for std Haskell syntax

   What does this mean, actually? Better support for standard
  Haskell syntax than what?

 --
 Jason Dusek




-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
1219 NW 83rd St
Seattle, WA 98117

+1 206.650.3740

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


Re: [Haskell-cafe] [ANN] full-sessions: yet another implementation of session types

2009-06-25 Thread Jason Dusek
  Having read some of the material, it seems that sessions are
  far richer than would be needed for most coroutines.

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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread Wei Hu
On Thu, Jun 25, 2009 at 1:10 PM, David Menendezd...@zednenem.com wrote:
 On Thu, Jun 25, 2009 at 12:17 PM, Wei Huwei@gmail.com wrote:
 Could you or anyone else briefly explain how mmtl solves the
 combinatorical explosion problem? Reading the source code is not very
 productive for newbies like me. Thanks!

 It's a good question, since from what I can tell mmtl does not solve
 the problem.

 Some quick background: If you have M monad transformers and N classes
 of operations, you normally need M*N instance declarations, i.e., one
 per transformer per class. Each instance either provides the
 functionality directly, such as the MonadState instance for StateT, or
 promotes it from the underlying monad, such as the MonadState instance
 for ReaderT.

 mmtl instead provides 2*M instances. For each transformer, it has one
 direct instance (such as MonadState (StateT s m)) and one instance
 which promotes through any transformer (such as MonadState (t (StateT
 s m))).

 The problem is that this limits you to using at most two transformers
 at a time. For example, the type ErrorT String (ReaderT Int (StateT
 Int m)) is an instance of MonadError and MonadReader, but not
 MonadState because it doesn't have the form t (StateT s m).

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/



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


Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-25 Thread wren ng thornton

Bulat Ziganshin wrote:

Hello wren,

Thursday, June 25, 2009, 6:35:36 AM, you wrote:


Rank2Types, RankNTypes, ExistentialQuantification, ScopedTypeVariables,
and GADTs are fairly benign ---though this is where you start loosing 
compatibility with non-GHC compilers.


afair, except for GADTs these are supported by Hugs. actually, until a
last few years, GHC and Hugs were pretty close on extensions list


True. I couldn't remember whether Hugs supported RankNTypes or not. In 
my mind all these extensions are of roughly the same bleeding-edge-ness, 
which is to say more than MPTCs and fundeps, but less than Template 
Haskell and type families. That's not entirely fair since GADTs are more 
bleeding-edge than Rank2Types (as witnessed by being GHC-only and still 
undecided on by the haskell' committee), and fundeps are still difficult 
to implement correctly, but all the same.


Haskell98 has a Hindley--Milner type system (more or less). My point was 
that once you start extending the type system as far as existential 
quantification, higher-order universal quantification, polymorphic 
components, existential components, GADTs, and the like then you've left 
HM so far behind that most Haskell compilers cannot keep up. UHC also 
supports Rank2Types/RankNTypes and ExistentialQuantification, though it 
doesn't support fundeps. I don't know how well nhc98, yhc, jhc, or lhc 
support options like these or what the timeline would be for offering 
such support. In short, this is where portability beyond GHC becomes spotty.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread wren ng thornton

Richard Silverman wrote:


Hi all,

I'm puzzled by something. Suppose I have some code that does lots of IO, 
and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* ugly 
-- the code is littered with lift functions!  Is there no cleaner way to 
do this?


Depending on the exact structure of your program, embracing imperativism 
may help. That is, you can use IORefs (or STRefs, or...) to store your 
global state instead of using StateT. Sometimes it helps, sometimes not; 
it depends a lot on the structure of the state, how fond you are of 
combinators, how you want to pass the IORefs down to the combinators,...



The cleanest approach to issues like this is usually to wrap a newtype 
wrapper around your specialty monad and use -XGeneralizedNewtypeDeriving 
to hoist all the layers up to the top. Or if you want to ensure 
portability then you can hand-write all the boilerplate instances for 
MonadFoo MyMonad. Depending on how you use IO, you'll want to mix this 
with judicious use of liftIO or define some wrappers or a typeclass for 
lifting your common IO functions to work on MyMonad.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generic Graph Class

2009-06-25 Thread Ivan Lazar Miljenovic

Some of us on #haskell last night (well, night for me :p) were
discussing this, and we're going to start a new project to implement an
extended version of my proposal.  The working project name is simply
graph (hey, we couldn't think of anything better!).  If you want to
join in the fun, talk to either myself (ivanm), Cale or mmorrow on
#haskell.

Ivan Miljenovic ivan.miljeno...@gmail.com writes:

 Yay, someone read my proposal! :p

 2009/6/25 Andrew Hunter andrewhhun...@gmail.com:
 This is a good idea and one I support.  (I think I've been told before
 that this has been tried w/o a lot of success, but, well...)  My
 primary concern is this: you built your class for things that operate
 on graphs...but there isn't a great distinction.  There are too many
 useful graph algorithms that require modification, or at least marking
 of vertices/edges (as taken, seen, by distance, color...think and
 you'll notice this happens everywhere.)  Thus, it'd be very nice if
 the Graph class could have a concept of:

 I was thinking about this, because graphviz at the moment uses the
 label field of nodes to determine which cluster it belongs to, etc.
 However, the problem with this is that Data.Graph doesn't have any
 labels...

 a) some amount of modification--new vertex, additional edge, what have you...

 Data.Graph can't really be modified in terms of adding a new vertex,
 unless you go and expand the array it uses and copy everything over
 (adding a new vertex, however, is indeed possible).

 b) Labeling of vertices/edges, ideally parameterized by label type.

 As I said, Data.Graph doesn't have any concept of labels; besides,
 this will require MultiParamTypeClasses and FunDeps AFAICT (and we
 should probably try to make this compatible with Haskell98 rather than
 using extensions).

 c) some amount of modification of those marks, so we can run, say,
 DFS, Floyd-Warshall, Dijsktra, Prims without cumbersome external
 management of secondary data structures.  This might require the
 definition of a GraphAlgorithm monad, which I've been toying with for
 a while--I'll see if I can dig up the code if there's desire.

 My original thoughts (which I didn't include with the proposal) was
 that algorithms _would_ use internal state.  My main impetus of
 thinking about this class was graphviz and hgal, which already use an
 internal state anyway (well, maybe not hgal as much; I've been trying
 to work my way through it a bit at a time now and then trying to
 improve its efficiency for what I need).

 Admittedly, it might be nice to have these extra features; it just
 might not be practical if we want the widest possible audience of
 the class.  The other alternative is if we have a second class that
 allows for updates, etc. but requires the first class as a dependency.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe